persistent-event-source-0.1.0: Persistent based event sourcing.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.Esqueleto.Monad.Experimental

Description

Classy shim around Database.Esqueleto.Experimental

In the style of Database.Persist.Monad, this exposes a "classy" (typeclass-using) API for Esqueleto functions, allowing them to be used with MonadSqlQuery constraints rather than a ReaderT SqlBackend concrete type.

The goal of this module is to be a drop-in replacement for Database.Esqueleto.Experimental.

Synopsis

Documentation

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

Avoid N+1 queries and join entities into a map structure.

This function is useful to call on the result of a single JOIN. For example, suppose you have this query:

getFoosAndNestedBarsFromParent
    :: ParentId
    -> SqlPersistT IO [(Entity Foo, Maybe (Entity Bar))]
getFoosAndNestedBarsFromParent parentId =
    select $ do
        (foo :& bar) <- from $
            table Foo
            `LeftOuterJoin`
            table Bar
                `on` do
                    \(foo :& bar) ->
                        foo ^. FooId ==. bar ?. BarFooId
        where_ $
            foo ^. FooParentId ==. val parentId
        pure (foo, bar)

This is a natural result type for SQL - a list of tuples. However, it's not what we usually want in Haskell - each Foo in the list will be represented multiple times, once for each Bar.

We can write fmap associateJoin and it will translate it into a Map that is keyed on the Key of the left Entity, and the value is a tuple of the entity's value as well as the list of each coresponding entity.

getFoosAndNestedBarsFromParentHaskellese
    :: ParentId
    -> SqlPersistT (Map (Key Foo) (Foo, [Maybe (Entity Bar)]))
getFoosAndNestedBarsFromParentHaskellese parentId =
    fmap associateJoin $ getFoosdAndNestedBarsFromParent parentId

What if you have multiple joins?

Let's use associateJoin with a *two* join query.

userPostComments
    :: SqlQuery (SqlExpr (Entity User, Entity Post, Entity Comment))
userPostsComment = do
    (u :& p :& c) <- from $
        table User
        `InnerJoin`
        table Post
            on do
                \(u :& p) ->
                    u ^. UserId ==. p ^. PostUserId
        `InnerJoin`
        table @Comment
            `on` do
                \(_ :& p :& c) ->
                    p ^. PostId ==. c ^. CommentPostId
    pure (u, p, c)

This query returns a User, with all of the users Posts, and then all of the Comments on that post.

First, we *nest* the tuple.

nest :: (a, b, c) -> (a, (b, c))
nest (a, b, c) = (a, (b, c))

This makes the return of the query conform to the input expected from associateJoin.

nestedUserPostComments
    :: SqlPersistT IO [(Entity User, (Entity Post, Entity Comment))]
nestedUserPostComments =
    fmap nest $ select userPostsComments

Now, we can call associateJoin on it.

associateUsers
    :: [(Entity User, (Entity Post, Entity Comment))]
    -> Map UserId (User, [(Entity Post, Entity Comment)])
associateUsers =
    associateJoin

Next, we'll use the Functor instances for Map and tuple to call associateJoin on the [(Entity Post, Entity Comment)].

associatePostsAndComments
    :: Map UserId (User, [(Entity Post, Entity Comment)])
    -> Map UserId (User, Map PostId (Post, [Entity Comment]))
associatePostsAndComments =
    fmap (fmap associateJoin)

For more reading on this topic, see this Foxhound Systems blog post.

Since: esqueleto-3.1.2

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

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

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

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: esqueleto-1.4.2

insertSelectCount :: forall (m :: Type -> Type) a backend. (MonadIO m, PersistEntity a, SqlBackendCanWrite backend) => SqlQuery (SqlExpr (Insertion a)) -> ReaderT backend m Int64 #

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

insertSelect :: forall (m :: Type -> Type) a backend. (MonadIO m, PersistEntity a, SqlBackendCanWrite backend) => SqlQuery (SqlExpr (Insertion a)) -> ReaderT backend m () #

Insert a PersistField for every selected value.

Since: esqueleto-2.4.2

renderQueryInsertInto #

Arguments

:: forall a r backend (m :: Type -> Type). (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.

Since: esqueleto-3.1.1

renderQueryUpdate #

Arguments

:: forall a r backend (m :: Type -> Type). (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.

Since: esqueleto-3.1.1

renderQueryDelete #

Arguments

:: forall a r backend (m :: Type -> Type). (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.

Since: esqueleto-3.1.1

renderQueryToText #

Arguments

:: forall a r backend (m :: Type -> Type). (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: esqueleto-3.1.1

updateCount :: forall (m :: Type -> Type) val backend. (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val), SqlBackendCanWrite backend) => (SqlExpr (Entity val) -> SqlQuery ()) -> ReaderT backend m Int64 #

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

deleteCount :: forall (m :: Type -> Type) backend. (MonadIO m, SqlBackendCanWrite backend) => SqlQuery () -> ReaderT backend m Int64 #

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

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

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

else_ :: expr a -> expr a #

Syntax sugar for case_.

Since: esqueleto-2.1.2

then_ :: () #

Syntax sugar for case_.

Since: esqueleto-2.1.2

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

Syntax sugar for case_.

Since: esqueleto-2.1.2

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

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

In this example, Bar is said to be the BaseEnt(ity), and Foo the child. To model this in Esqueleto, declare:

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

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: esqueleto-2.4.3

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

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: esqueleto-2.1.2

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

Apply extra SqlExpr Value arguments to a PersistField constructor

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

Apply a PersistField constructor to SqlExpr Value arguments.

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

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

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

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

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

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

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.

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

NOT EXISTS operator.

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

EXISTS operator. For example:

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

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

NOT IN operator.

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

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

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

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: esqueleto-2.2.12

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

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

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

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

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

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.

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

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

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

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

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

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" ++. (%)

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

ILIKE operator (case-insensitive LIKE).

Supported by PostgreSQL only.

Since: esqueleto-2.2.3

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

LIKE operator.

right_ :: (SqlString s, Num a) => (SqlExpr (Value s), SqlExpr (Value a)) -> SqlExpr (Value s) #

RIGHT function. @since 3.3.0

left_ :: (SqlString s, Num a) => (SqlExpr (Value s), SqlExpr (Value a)) -> SqlExpr (Value s) #

LEFT function. @since 3.3.0

length_ :: (SqlString s, Num a) => SqlExpr (Value s) -> SqlExpr (Value a) #

LENGTH function. @since 3.3.0

ltrim_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) #

LTRIM function. @since 3.3.0

rtrim_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) #

RTRIM function. @since 3.3.0

trim_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) #

TRIM function. @since 3.3.0

upper_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) #

UPPER function. @since 3.3.0

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

LOWER function.

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

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

Since: esqueleto-1.4.3

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

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: esqueleto-1.4.3

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

Same as castNum, but for nullable values.

Since: esqueleto-2.2.9

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

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: esqueleto-2.2.9

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

BETWEEN.

@since: 3.1.0

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

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

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

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

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

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

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

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

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

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

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

COUNT(DISTINCT x).

Since: esqueleto-2.4.1

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

COUNT.

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

COUNT(*) value.

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

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

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

NULL value.

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

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

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

IS NULL comparison.

For IS NOT NULL, you can negate this with not_, as in not_ (isNothing (person ^. PersonAge))

Warning: Persistent and Esqueleto have different behavior for != Nothing:

HaskellSQL
Persistent!=. NothingIS NOT NULL
Esqueleto!=. Nothing!= NULL

In SQL, = NULL and != NULL return NULL instead of true or false. For this reason, you very likely do not want to use !=. Nothing in Esqueleto. You may find these hlint rules helpful to enforce this:

- error: {lhs: v Database.Esqueleto.==. Database.Esqueleto.nothing, rhs: Database.Esqueleto.isNothing v, name: Use Esqueleto's isNothing}
- error: {lhs: v Database.Esqueleto.==. Database.Esqueleto.val Nothing, rhs: Database.Esqueleto.isNothing v, name: Use Esqueleto's isNothing}
- error: {lhs: v Database.Esqueleto.!=. Database.Esqueleto.nothing, rhs: not_ (Database.Esqueleto.isNothing v), name: Use Esqueleto's not isNothing}
- error: {lhs: v Database.Esqueleto.!=. Database.Esqueleto.val Nothing, rhs: not_ (Database.Esqueleto.isNothing v), name: Use Esqueleto's not isNothing}

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

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

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

Project a field of an entity that may be null.

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

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

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

Project a field of an entity.

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

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: esqueleto-3.2.0

subSelectForeign #

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: esqueleto-3.2.0

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

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: esqueleto-3.2.0

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

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: esqueleto-3.2.0

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

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: esqueleto-3.2.0

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

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: esqueleto-3.2.0

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

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.

locking :: LockingKind -> SqlQuery () #

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: esqueleto-2.2.7

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

HAVING.

Since: esqueleto-1.2.2

rand :: SqlExpr OrderBy #

ORDER BY random() clause.

Since: esqueleto-1.3.10

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

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: esqueleto-2.2.4

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

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

Since: esqueleto-2.2.4

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

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: esqueleto-2.2.4

distinct :: SqlQuery a -> SqlQuery a #

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: esqueleto-2.2.4

offset :: Int64 -> SqlQuery () #

OFFSET. Usually used with limit.

limit :: Int64 -> SqlQuery () #

LIMIT. Limit the number of returned rows.

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

Descending order of this field or SqlExpression.

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

Ascending order of this field or SqlExpression.

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

ORDER BY clause. See also asc and desc.

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

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

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)

Need more columns?

The ToSomeValues class is defined for SqlExpr and tuples of SqlExprs. We only have definitions for up to 8 elements in a tuple right now, so it's possible that you may need to have more than 8 elements.

For example, consider a query with a groupBy call like this:

groupBy (e0, e1, e2, e3, e4, e5, e6, e7)

This is the biggest you can get with a single tuple. However, you can easily nest the tuples to add more:

groupBy ((e0, e1, e2, e3, e4, e5, e6, e7), e8, e9)

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

WHERE clause: restrict the query's result.

newtype Value a #

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

Constructors

Value 

Fields

Instances

Instances details
Applicative Value 
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 #

Functor Value

Since: esqueleto-1.4.4

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Monad Value 
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 #

(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Entity rec)) (SqlExpr (Value typ))

This instance allows you to use record.field notation with GHC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
BlogPost
    authorId     PersonId
    title        Text

-- query:
select $ do
    bp <- from $ table @BlogPost
    pure $ bp.title

This is exactly equivalent to the following:

blogPost :: SqlExpr (Entity BlogPost)

blogPost ^. BlogPostTitle
blogPost ^. #title
blogPost.title

There's another instance defined on SqlExpr (Entity (Maybe rec)), which allows you to project from a LEFT JOINed entity.

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Entity rec) -> SqlExpr (Value typ) #

(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Maybe (Entity rec))) (SqlExpr (Value (Maybe typ)))

This instance allows you to use record.field notation with GC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
Person
    name         Text

BlogPost
    title        Text
    authorId     PersonId

-- query:

select $ do
    (p :& bp) <- from $
        table Person
        leftJoin table BlogPost
        on do
            \(p :& bp) ->
                just p.id ==. bp.authorId
    pure (p.name, bp.title)

The following forms are all equivalent:

blogPost :: SqlExpr (Maybe (Entity BlogPost))

blogPost ?. BlogPostTitle
blogPost ?. #title
blogPost.title

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Maybe (Entity rec)) -> SqlExpr (Value (Maybe typ)) #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b, d ~ (a' :& b)) => DoInnerJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doInnerJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d #

(ToFrom a a', ToMaybe b, d ~ (a' :& ToMaybeT b), SqlSelect b r, ToAlias b, ToAliasReference b) => DoLeftJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doLeftJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d #

Show a => Show (Value a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

show :: Value a -> String #

showList :: [Value a] -> ShowS #

ToAlias (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a)) #

ToAliasReference (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToMaybe (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Value a)) #

Methods

toMaybe :: SqlExpr (Value a) -> ToMaybeT (SqlExpr (Value a)) #

ToSomeValues (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toSomeValues :: SqlExpr (Value a) -> [SomeValue] #

Eq a => Eq (Value a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Ord a => Ord (Value a) 
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 #

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

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

Instance details

Defined in Database.Esqueleto.Internal.Internal

type ToMaybeT (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

newtype ValueList a #

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

Instances details
Show a => Show (ValueList a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Eq a => Eq (ValueList a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Ord a => Ord (ValueList a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

data InnerJoin a b infixl 2 #

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

Constructors

a `InnerJoin` b infixl 2 

Instances

Instances details
IsJoinKind InnerJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

smartJoin :: a -> b -> InnerJoin a b #

reifyJoinKind :: InnerJoin a b -> JoinKind #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (InnerJoin a b) #

data CrossJoin a b infixl 2 #

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

Constructors

a `CrossJoin` b infixl 2 

Instances

Instances details
IsJoinKind CrossJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

smartJoin :: a -> b -> CrossJoin a b #

reifyJoinKind :: CrossJoin a b -> JoinKind #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (CrossJoin a b) #

data LeftOuterJoin a b infixl 2 #

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 

Instances

Instances details
IsJoinKind LeftOuterJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

smartJoin :: a -> b -> LeftOuterJoin a b #

reifyJoinKind :: LeftOuterJoin a b -> JoinKind #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (LeftOuterJoin a b) #

data RightOuterJoin a b infixl 2 #

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

Constructors

a `RightOuterJoin` b infixl 2 

Instances

Instances details
IsJoinKind RightOuterJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (RightOuterJoin a b) #

data FullOuterJoin a b infixl 2 #

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

Constructors

a `FullOuterJoin` b infixl 2 

Instances

Instances details
IsJoinKind FullOuterJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

smartJoin :: a -> b -> FullOuterJoin a b #

reifyJoinKind :: FullOuterJoin a b -> JoinKind #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (FullOuterJoin a b) #

data JoinKind #

(Internal) A kind of JOIN.

Constructors

InnerJoinKind
INNER JOIN
CrossJoinKind
CROSS JOIN
LeftOuterJoinKind
LEFT OUTER JOIN
RightOuterJoinKind
RIGHT OUTER JOIN
FullOuterJoinKind
FULL OUTER JOIN

Instances

Instances details
Show JoinKind 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Eq JoinKind 
Instance details

Defined in Database.Esqueleto.Internal.Internal

data OnClauseWithoutMatchingJoinException #

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

Instances

Instances details
Exception OnClauseWithoutMatchingJoinException 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Show OnClauseWithoutMatchingJoinException 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Eq OnClauseWithoutMatchingJoinException 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Ord OnClauseWithoutMatchingJoinException 
Instance details

Defined in Database.Esqueleto.Internal.Internal

data OrderBy #

Phantom type used by orderBy, asc and desc.

data DistinctOn #

Phantom type used by distinctOn and don.

data LockingKind #

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: esqueleto-2.2.7

Constructors

ForUpdate

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

Since: esqueleto-2.2.7

ForUpdateSkipLocked

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

Since: esqueleto-2.2.7

ForShare

FOR SHARE syntax. Supported by PostgreSQL.

Since: esqueleto-2.2.7

LockInShareMode

LOCK IN SHARE MODE syntax. Supported by MySQL.

Since: esqueleto-2.2.7

class PersistField a => SqlString a #

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: esqueleto-2.4.0

Instances

Instances details
SqlString Html

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString ByteString

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString Text

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString Text

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString a => SqlString (Maybe a)

Since: esqueleto-2.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

a ~ Char => SqlString [a]

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

type family BaseEnt ent #

e.g. type BaseEnt MyBase = MyChild

class ToBaseId ent where #

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 #

e.g. type BaseEnt MyBase = MyChild

Methods

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

Convert from the key of the BaseEnt(ity) to the key of the child entity. This function is not actually called, but that it typechecks proves this operation is safe.

data SqlQuery a #

SQL backend for esqueleto using SqlPersistT.

Instances

Instances details
Applicative SqlQuery 
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 #

Functor SqlQuery 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Monad SqlQuery 
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 #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b, d ~ (a' :& b)) => DoInnerJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doInnerJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d #

(ToFrom a a', ToMaybe b, d ~ (a' :& ToMaybeT b), SqlSelect b r, ToAlias b, ToAliasReference b) => DoLeftJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doLeftJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b) => DoCrossJoin Lateral a (a' -> SqlQuery b) (a' :& b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doCrossJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b) -> From (a' :& b) #

(SqlSelect a r, ToAlias a, ToAliasReference a) => ToFrom (SubQuery (SqlQuery a)) a 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: SubQuery (SqlQuery a) -> From a #

(SqlSelect a r, ToAlias a, ToAliasReference a) => ToFrom (SqlQuery a) a 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: SqlQuery a -> From a #

(SqlSelect a r, ToAlias a, ToAliasReference a) => ToSqlSetOperation (SqlQuery a) a 
Instance details

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

ValidOnClause (a -> SqlQuery b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

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

Constraint synonym for persistent entities whose backend is SqlBackend.

data SqlExpr a #

An expression on the SQL backend.

Raw expression: Contains a SqlExprMeta and a function for building the expr. It recieves a parameter telling it whether it is in a parenthesized context, and takes information about the SQL connection (mainly for escaping names) and returns both an string (Builder) and a list of values to be interpolated by the SQL backend.

Instances

Instances details
(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Entity rec)) (SqlExpr (Value typ))

This instance allows you to use record.field notation with GHC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
BlogPost
    authorId     PersonId
    title        Text

-- query:
select $ do
    bp <- from $ table @BlogPost
    pure $ bp.title

This is exactly equivalent to the following:

blogPost :: SqlExpr (Entity BlogPost)

blogPost ^. BlogPostTitle
blogPost ^. #title
blogPost.title

There's another instance defined on SqlExpr (Entity (Maybe rec)), which allows you to project from a LEFT JOINed entity.

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Entity rec) -> SqlExpr (Value typ) #

(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Maybe (Entity rec))) (SqlExpr (Value (Maybe typ)))

This instance allows you to use record.field notation with GC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
Person
    name         Text

BlogPost
    title        Text
    authorId     PersonId

-- query:

select $ do
    (p :& bp) <- from $
        table Person
        leftJoin table BlogPost
        on do
            \(p :& bp) ->
                just p.id ==. bp.authorId
    pure (p.name, bp.title)

The following forms are all equivalent:

blogPost :: SqlExpr (Maybe (Entity BlogPost))

blogPost ?. BlogPostTitle
blogPost ?. #title
blogPost.title

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Maybe (Entity rec)) -> SqlExpr (Value (Maybe typ)) #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b, d ~ (a' :& b)) => DoInnerJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doInnerJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d #

(ToFrom a a', ToMaybe b, d ~ (a' :& ToMaybeT b), SqlSelect b r, ToAlias b, ToAliasReference b) => DoLeftJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doLeftJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d #

ToAlias (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a)) #

ToAlias (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a)) #

ToAlias (SqlExpr (Maybe (Entity a))) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Maybe (Entity a)) -> SqlQuery (SqlExpr (Maybe (Entity a))) #

ToAliasReference (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToAliasReference (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToAliasReference (SqlExpr (Maybe (Entity a))) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToMaybe (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Value a)) #

Methods

toMaybe :: SqlExpr (Value a) -> ToMaybeT (SqlExpr (Value a)) #

ToMaybe (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Entity a)) #

Methods

toMaybe :: SqlExpr (Entity a) -> ToMaybeT (SqlExpr (Entity a)) #

ToMaybe (SqlExpr (Maybe a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Maybe a)) #

Methods

toMaybe :: SqlExpr (Maybe a) -> ToMaybeT (SqlExpr (Maybe a)) #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

ToSomeValues (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toSomeValues :: SqlExpr (Value a) -> [SomeValue] #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

PersistEntity ent => ToFrom (Table ent) (SqlExpr (Entity ent)) 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: Table ent -> From (SqlExpr (Entity ent)) #

PersistEntity e => SqlSelect (SqlExpr (Insertion e)) (Insertion e)

INSERT INTO hack.

Instance details

Defined in Database.Esqueleto.Internal.Internal

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

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

Instance details

Defined in Database.Esqueleto.Internal.Internal

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

You may return an Entity from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

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

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

Instance details

Defined in Database.Esqueleto.Internal.Internal

type ToMaybeT (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (SqlExpr (Maybe a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

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 #

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

Instances details
(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) #

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 PersistConfigBackend c :: (Type -> Type) -> Type -> Type #

Instances

Instances details
type PersistConfigBackend (Either c1 c2) 
Instance details

Defined in Database.Persist.Class.PersistConfig

type family PersistConfigPool c #

Instances

Instances details
type PersistConfigPool (Either c1 c2) 
Instance details

Defined in Database.Persist.Class.PersistConfig

newtype ConstraintNameHS #

An ConstraintNameHS represents the Haskell-side name that persistent will use for a constraint.

Since: persistent-2.12.0.0

Constructors

ConstraintNameHS 

newtype ConstraintNameDB #

A ConstraintNameDB represents the datastore-side name that persistent will use for a constraint.

Since: persistent-2.12.0.0

Constructors

ConstraintNameDB 

Instances

Instances details
Read ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

Show ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

Eq ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

Ord ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

DatabaseName ConstraintNameDB

Since: persistent-2.12.0.0

Instance details

Defined in Database.Persist.Names

Methods

escapeWith :: (Text -> str) -> ConstraintNameDB -> str #

Lift ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

Methods

lift :: Quote m => ConstraintNameDB -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ConstraintNameDB -> Code m ConstraintNameDB #

newtype EntityNameDB #

An EntityNameDB represents the datastore-side name that persistent will use for an entity.

Since: persistent-2.12.0.0

Constructors

EntityNameDB 

Fields

newtype EntityNameHS #

An EntityNameHS represents the Haskell-side name that persistent will use for an entity.

Since: persistent-2.12.0.0

Constructors

EntityNameHS 

Fields

newtype FieldNameHS #

A FieldNameHS represents the Haskell-side name that persistent will use for a field.

Since: persistent-2.12.0.0

Constructors

FieldNameHS 

Fields

newtype FieldNameDB #

An EntityNameDB represents the datastore-side name that persistent will use for an entity.

Since: persistent-2.12.0.0

Constructors

FieldNameDB 

Fields

Instances

Instances details
Read FieldNameDB 
Instance details

Defined in Database.Persist.Names

Show FieldNameDB 
Instance details

Defined in Database.Persist.Names

Eq FieldNameDB 
Instance details

Defined in Database.Persist.Names

Ord FieldNameDB 
Instance details

Defined in Database.Persist.Names

DatabaseName FieldNameDB

Since: persistent-2.12.0.0

Instance details

Defined in Database.Persist.Names

Methods

escapeWith :: (Text -> str) -> FieldNameDB -> str #

Lift FieldNameDB 
Instance details

Defined in Database.Persist.Names

Methods

lift :: Quote m => FieldNameDB -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FieldNameDB -> Code m FieldNameDB #

class DatabaseName a where #

Convenience operations for working with '-NameDB' types.

Since: persistent-2.12.0.0

Methods

escapeWith :: (Text -> str) -> a -> str #

Instances

Instances details
DatabaseName ConstraintNameDB

Since: persistent-2.12.0.0

Instance details

Defined in Database.Persist.Names

Methods

escapeWith :: (Text -> str) -> ConstraintNameDB -> str #

DatabaseName EntityNameDB 
Instance details

Defined in Database.Persist.Names

Methods

escapeWith :: (Text -> str) -> EntityNameDB -> str #

DatabaseName FieldNameDB

Since: persistent-2.12.0.0

Instance details

Defined in Database.Persist.Names

Methods

escapeWith :: (Text -> str) -> FieldNameDB -> str #

data LiteralType #

A type that determines how a backend should handle the literal.

Since: persistent-2.12.0.0

Constructors

Escaped

The accompanying value will be escaped before inserting into the database. This is the correct default choice to use.

Since: persistent-2.12.0.0

Unescaped

The accompanying value will not be escaped when inserting into the database. This is potentially dangerous - use this with care.

Since: persistent-2.12.0.0

DbSpecific

The DbSpecific constructor corresponds to the legacy PersistDbSpecific constructor. We need to keep this around because old databases may have serialized JSON representations that reference this. We don't want to break the ability of a database to load rows.

Since: persistent-2.12.0.0

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

PersistLiteral_ LiteralType ByteString

This constructor is used to specify some raw literal value for the backend. The LiteralType value specifies how the value should be escaped. This can be used to make special, custom types avaialable in the back end.

Since: persistent-2.12.0.0

Bundled Patterns

pattern PersistLiteral :: ByteString -> PersistValue

This pattern synonym used to be a data constructor on PersistValue, but was changed into a catch-all pattern synonym to allow backwards compatiblity with database types. See the documentation on PersistDbSpecific for more details.

Since: persistent-2.12.0.0

pattern PersistDbSpecific :: ByteString -> PersistValue

This pattern synonym used to be a data constructor for the PersistValue type. It was changed to be a pattern so that JSON-encoded database values could be parsed into their corresponding values. You should not use this, and instead prefer to pattern match on PersistLiteral_ directly.

If you use this, it will overlap a patern match on the 'PersistLiteral_, PersistLiteral, and PersistLiteralEscaped patterns. If you need to disambiguate between these constructors, pattern match on PersistLiteral_ directly.

Since: persistent-2.12.0.0

pattern PersistLiteralEscaped :: ByteString -> PersistValue

This pattern synonym used to be a data constructor on PersistValue, but was changed into a catch-all pattern synonym to allow backwards compatiblity with database types. See the documentation on PersistDbSpecific for more details.

Since: persistent-2.12.0.0

Instances

Instances details
FromJSON PersistValue 
Instance details

Defined in Database.Persist.PersistValue

ToJSON PersistValue 
Instance details

Defined in Database.Persist.PersistValue

Read PersistValue 
Instance details

Defined in Database.Persist.PersistValue

Show PersistValue 
Instance details

Defined in Database.Persist.PersistValue

Eq PersistValue 
Instance details

Defined in Database.Persist.PersistValue

Ord PersistValue 
Instance details

Defined in Database.Persist.PersistValue

FromHttpApiData PersistValue 
Instance details

Defined in Database.Persist.PersistValue

ToHttpApiData PersistValue 
Instance details

Defined in Database.Persist.PersistValue

PathPiece PersistValue 
Instance details

Defined in Database.Persist.PersistValue

PersistField PersistValue 
Instance details

Defined in Database.Persist.Class.PersistField

PersistFieldSql PersistValue 
Instance details

Defined in Database.Persist.Sql.Class

data IsolationLevel #

Please refer to the documentation for the database in question for a full overview of the semantics of the varying isloation levels

Instances

Instances details
Bounded IsolationLevel 
Instance details

Defined in Database.Persist.SqlBackend.Internal.IsolationLevel

Enum IsolationLevel 
Instance details

Defined in Database.Persist.SqlBackend.Internal.IsolationLevel

Show IsolationLevel 
Instance details

Defined in Database.Persist.SqlBackend.Internal.IsolationLevel

Eq IsolationLevel 
Instance details

Defined in Database.Persist.SqlBackend.Internal.IsolationLevel

Ord IsolationLevel 
Instance details

Defined in Database.Persist.SqlBackend.Internal.IsolationLevel

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

Instances

Instances details
Read FieldDef 
Instance details

Defined in Database.Persist.Types.Base

Show FieldDef 
Instance details

Defined in Database.Persist.Types.Base

Eq FieldDef 
Instance details

Defined in Database.Persist.Types.Base

Ord FieldDef 
Instance details

Defined in Database.Persist.Types.Base

Lift FieldDef 
Instance details

Defined in Database.Persist.Types.Base

Methods

lift :: Quote m => FieldDef -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FieldDef -> Code m FieldDef #

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

Instances

Instances details
Read SqlType 
Instance details

Defined in Database.Persist.Types.Base

Show SqlType 
Instance details

Defined in Database.Persist.Types.Base

Eq SqlType 
Instance details

Defined in Database.Persist.Types.Base

Methods

(==) :: SqlType -> SqlType -> Bool #

(/=) :: SqlType -> SqlType -> Bool #

Ord SqlType 
Instance details

Defined in Database.Persist.Types.Base

Lift SqlType 
Instance details

Defined in Database.Persist.Types.Base

Methods

lift :: Quote m => SqlType -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => SqlType -> Code m SqlType #

data FieldCascade #

This datatype describes how a foreign reference field cascades deletes or updates.

This type is used in both parsing the model definitions and performing migrations. A Nothing in either of the field values means that the user has not specified a CascadeAction. An unspecified CascadeAction is defaulted to Restrict when doing migrations.

Since: persistent-2.11.0

data ForeignDef #

Constructors

ForeignDef 

Fields

type ForeignFieldDef = (FieldNameHS, FieldNameDB) #

Used instead of FieldDef to generate a smaller amount of code

data UniqueDef #

Type for storing the Uniqueness constraint in the Schema. Assume you have the following schema with a uniqueness constraint:

Person
  name String
  age Int
  UniqueAge age

This will be represented as:

UniqueDef
    { uniqueHaskell = ConstraintNameHS (packPTH UniqueAge)
    , uniqueDBName = ConstraintNameDB (packPTH "unique_age")
    , uniqueFields = [(FieldNameHS (packPTH "age"), FieldNameDB (packPTH "age"))]
    , uniqueAttrs = []
    }

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 

data EmbedEntityDef #

An EmbedEntityDef is the same as an EntityDef But it is only used for fieldReference so it only has data needed for embedding

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 !EntityNameHS

A ForeignRef has a late binding to the EntityDef it references via name and has the Haskell type of the foreign key in the form of FieldType

EmbedRef EntityNameHS 
CompositeRef CompositeDef 
SelfReference

A SelfReference stops an immediate cycle which causes non-termination at compile-time (issue #311).

data FieldType #

A FieldType describes a field parsed from the QuasiQuoter and is used to determine the Haskell type in the generated code.

name Text parses into FTTypeCon Nothing Text

name T.Text parses into FTTypeCon (Just T Text)

name (Jsonb User) parses into:

FTApp (FTTypeCon Nothing Jsonb) (FTTypeCon Nothing User)

Constructors

FTTypeCon (Maybe Text) Text

Optional module and name.

FTTypePromoted Text 
FTApp FieldType FieldType 
FTList FieldType 

data FieldAttr #

Attributes that may be attached to fields that can affect migrations and serialization in backend-specific ways.

While we endeavor to, we can't forsee all use cases for all backends, and so FieldAttr is extensible through its constructor FieldAttrOther.

Since: persistent-2.11.0.0

Constructors

FieldAttrMaybe

The Maybe keyword goes after the type. This indicates that the column is nullable, and the generated Haskell code will have a Maybe type for it.

Example:

User
    name Text Maybe
FieldAttrNullable

This indicates that the column is nullable, but should not have a Maybe type. For this to work out, you need to ensure that the PersistField instance for the type in question can support a PersistNull value.

data What = NoWhat | Hello Text

instance PersistField What where
    fromPersistValue PersistNull =
        pure NoWhat
    fromPersistValue pv =
        Hello $ fromPersistValue pv

instance PersistFieldSql What where
    sqlType _ = SqlString

User
    what What nullable
FieldAttrMigrationOnly

This tag means that the column will not be present on the Haskell code, but will not be removed from the database. Useful to deprecate fields in phases.

You should set the column to be nullable in the database. Otherwise, inserts won't have values.

User
    oldName Text MigrationOnly
    newName Text
FieldAttrSafeToRemove

A SafeToRemove attribute is not present on the Haskell datatype, and the backend migrations should attempt to drop the column without triggering any unsafe migration warnings.

Useful after you've used MigrationOnly to remove a column from the database in phases.

User
    oldName Text SafeToRemove
    newName Text
FieldAttrNoreference

This attribute indicates that we should create a foreign key reference from a column. By default, persistent will try and create a foreign key reference for a column if it can determine that the type of the column is a Key entity or an EntityId and the Entity's name was present in mkPersist.

This is useful if you want to use the explicit foreign key syntax.

Post
    title    Text

Comment
    postId   PostId      noreference
    Foreign Post fk_comment_post postId
FieldAttrReference Text

This is set to specify precisely the database table the column refers to.

Post
    title    Text

Comment
    postId   PostId references="post"

You should not need this - persistent should be capable of correctly determining the target table's name. If you do need this, please file an issue describing why.

FieldAttrConstraint Text

Specify a name for the constraint on the foreign key reference for this table.

Post
    title    Text

Comment
    postId   PostId constraint="my_cool_constraint_name"
FieldAttrDefault Text

Specify the default value for a column.

User
    createdAt    UTCTime     default="NOW()"

Note that a default= attribute does not mean you can omit the value while inserting.

FieldAttrSqltype Text

Specify a custom SQL type for the column. Generally, you should define a custom datatype with a custom PersistFieldSql instance instead of using this.

User
    uuid     Text    sqltype=UUID
FieldAttrMaxlen Integer

Set a maximum length for a column. Useful for VARCHAR and indexes.

User
    name     Text    maxlen=200

    UniqueName name
FieldAttrSql Text

Specify the database name of the column.

User
    blarghle     Int     sql="b_l_a_r_g_h_l_e"

Useful for performing phased migrations, where one column is renamed to another column over time.

FieldAttrOther Text

A grab bag of random attributes that were unrecognized by the parser.

type Attr = Text #

type ExtraLine = [Text] #

data EntityIdDef #

The definition for the entity's primary key ID.

Since: persistent-2.13.0.0

Constructors

EntityIdField !FieldDef

The entity has a single key column, and it is a surrogate key - that is, you can't go from rec -> Key rec.

Since: persistent-2.13.0.0

EntityIdNaturalKey !CompositeDef

The entity has a natural key. This means you can write rec -> Key rec because all the key fields are present on the datatype.

A natural key can have one or more columns.

Since: persistent-2.13.0.0

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.

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.

Instances

Instances details
Show WhyNullable 
Instance details

Defined in Database.Persist.Types.Base

Eq WhyNullable 
Instance details

Defined in Database.Persist.Types.Base

data IsNullable #

Instances

Instances details
Show IsNullable 
Instance details

Defined in Database.Persist.Types.Base

Eq IsNullable 
Instance details

Defined in Database.Persist.Types.Base

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

Instances details
Bounded Checkmark 
Instance details

Defined in Database.Persist.Types.Base

Enum 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

Eq Checkmark 
Instance details

Defined in Database.Persist.Types.Base

Ord Checkmark 
Instance details

Defined in Database.Persist.Types.Base

FromHttpApiData Checkmark 
Instance details

Defined in Database.Persist.Types.Base

ToHttpApiData Checkmark 
Instance details

Defined in Database.Persist.Types.Base

PathPiece Checkmark 
Instance details

Defined in Database.Persist.Types.Base

PersistField Checkmark 
Instance details

Defined in Database.Persist.Class.PersistField

PersistFieldSql Checkmark 
Instance details

Defined in Database.Persist.Sql.Class

entitiesPrimary :: EntityDef -> NonEmpty FieldDef #

Return the [FieldDef] for the entity keys.

keyAndEntityFields :: EntityDef -> NonEmpty FieldDef #

Returns a NonEmpty list of FieldDef that correspond with the key columns for an EntityDef.

parseFieldAttrs :: [Text] -> [FieldAttr] #

Parse raw field attributes into structured form. Any unrecognized attributes will be preserved, identically as they are encountered, as FieldAttrOther values.

Since: persistent-2.11.0.0

isHaskellField :: FieldDef -> Bool #

Returns True if the FieldDef does not have a MigrationOnly or SafeToRemove flag from the QuasiQuoter.

Since: persistent-2.13.0.0

noCascade :: FieldCascade #

A FieldCascade that does nothing.

Since: persistent-2.11.0

renderFieldCascade :: FieldCascade -> Text #

Renders a FieldCascade value such that it can be used in SQL migrations.

Since: persistent-2.11.0

renderCascadeAction :: CascadeAction -> Text #

Render a CascadeAction to Text such that it can be used in a SQL command.

Since: persistent-2.11.0

data Statement #

A Statement is a representation of a database query that has been prepared and stored on the server side.

Constructors

Statement 

Fields

type LogFunc = Loc -> LogSource -> LogLevel -> LogStr -> IO () #

setFieldAttrs :: [FieldAttr] -> FieldDef -> FieldDef #

Replace the FieldDef FieldAttr with the new list.

Since: persistent-2.13.0.0

overFieldAttrs :: ([FieldAttr] -> [FieldAttr]) -> FieldDef -> FieldDef #

Modify the list of field attributes.

Since: persistent-2.13.0.0

addFieldAttr :: FieldAttr -> FieldDef -> FieldDef #

Add an attribute to the list of field attributes.

Since: persistent-2.13.0.0

isFieldNullable :: FieldDef -> IsNullable #

Check if the field definition is nullable

Since: persistent-2.13.0.0

isFieldMaybe :: FieldDef -> Bool #

Check if the field is `Maybe a`

Since: persistent-2.13.0.0

getEntityUniques :: EntityDef -> [UniqueDef] #

Retrieve the list of UniqueDef from an EntityDef. This currently does not include a Primary key, if one is defined. A future version of persistent will include a Primary key among the Unique constructors for the Entity.

Since: persistent-2.13.0.0

getEntityHaskellName :: EntityDef -> EntityNameHS #

Retrieve the Haskell name of the given entity.

Since: persistent-2.13.0.0

getEntityDBName :: EntityDef -> EntityNameDB #

Return the database name for the given entity.

Since: persistent-2.13.0.0

setEntityDBName :: EntityNameDB -> EntityDef -> EntityDef #

Since: persistent-2.13.0.0

getEntityForeignDefs :: EntityDef -> [ForeignDef] #

Since: persistent-2.13.0.0

getEntityFields :: EntityDef -> [FieldDef] #

Retrieve the list of FieldDef that makes up the fields of the entity.

This does not return the fields for an Id column or an implicit id. It will return the key columns if you used the Primary syntax for defining the primary key.

This does not return fields that are marked SafeToRemove or MigrationOnly - so it only returns fields that are represented in the Haskell type. If you need those fields, use getEntityFieldsDatabase.

Since: persistent-2.13.0.0

getEntityFieldsDatabase :: EntityDef -> [FieldDef] #

This returns all of the FieldDef defined for the EntityDef, including those fields that are marked as MigrationOnly (and therefore only present in the database) or SafeToRemove (and a migration will drop the column if it exists in the database).

For all the fields that are present on the Haskell-type, see getEntityFields.

Since: persistent-2.13.0.0

isEntitySum :: EntityDef -> Bool #

Since: persistent-2.13.0.0

getEntityId :: EntityDef -> EntityIdDef #

Since: persistent-2.13.0.0

getEntityIdField :: EntityDef -> Maybe FieldDef #

Since: persistent-2.13.0.0

setEntityId :: FieldDef -> EntityDef -> EntityDef #

Set an entityId to be the given FieldDef.

Since: persistent-2.13.0.0

setEntityIdDef :: EntityIdDef -> EntityDef -> EntityDef #

Since: persistent-2.13.0.0

getEntityKeyFields :: EntityDef -> NonEmpty FieldDef #

Since: persistent-2.13.0.0

overEntityFields :: ([FieldDef] -> [FieldDef]) -> EntityDef -> EntityDef #

Perform a mapping function over all of the entity fields, as determined by getEntityFieldsDatabase.

Since: persistent-2.13.0.0

newtype OverflowNatural #

Prior to persistent-2.11.0, we provided an instance of PersistField for the Natural type. This was in error, because Natural represents an infinite value, and databases don't have reasonable types for this.

The instance for Natural used the Int64 underlying type, which will cause underflow and overflow errors. This type has the exact same code in the instances, and will work seamlessly.

A more appropriate type for this is the Word series of types from Data.Word. These have a bounded size, are guaranteed to be non-negative, and are quite efficient for the database to store.

Since: persistent-2.11.0

Constructors

OverflowNatural 

Instances

Instances details
Num OverflowNatural 
Instance details

Defined in Database.Persist.Class.PersistField

Show OverflowNatural 
Instance details

Defined in Database.Persist.Class.PersistField

Eq OverflowNatural 
Instance details

Defined in Database.Persist.Class.PersistField

Ord OverflowNatural 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField OverflowNatural 
Instance details

Defined in Database.Persist.Class.PersistField

PersistFieldSql OverflowNatural

This type uses the SqlInt64 version, which will exhibit overflow and underflow behavior. Additionally, it permits negative values in the database, which isn't ideal.

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

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

Instances details
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 Int8 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Rational 
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 Html 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField ByteString 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField OverflowNatural 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField SomePersistField 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField PersistValue 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Checkmark 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Text 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Text 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Day 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField UTCTime 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField TimeOfDay 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Word8 
Instance details

Defined in Database.Persist.Class.PersistField

(TypeError ((((('Text "The instance of PersistField for the Natural type was removed." :$$: 'Text "Please see the documentation for OverflowNatural if you want to ") :$$: 'Text "continue using the old behavior or want to see documentation on ") :$$: 'Text "why the instance was removed.") :$$: 'Text "") :$$: 'Text "This error instance will be removed in a future release.") :: Constraint) => PersistField Natural 
Instance details

Defined in Database.Persist.Class.PersistField

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

PersistField a => PersistField (Maybe a) 
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

HasResolution a => PersistField (Fixed a) 
Instance details

Defined in Database.Persist.Class.PersistField

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

Defined in Database.Persist.Class.PersistField

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

Defined in Database.Persist.Class.PersistField

class SymbolToField (sym :: Symbol) rec typ | sym rec -> typ where #

This type class is used with the OverloadedLabels extension to provide a more convenient means of using the EntityField type. EntityField definitions are prefixed with the type name to avoid ambiguity, but this ambiguity can result in verbose code.

If you have a table User with a name Text field, then the corresponding EntityField is UserName. With this, we can write #name :: EntityField User Text.

What's more fun is that the type is more general: it's actually #name :: (SymbolToField "name" rec typ) => EntityField rec typ

Which means it is *polymorphic* over the actual record. This allows you to write code that can be generic over the tables, provided they have the right fields.

Since: persistent-2.11.0.0

Methods

symbolToField :: EntityField rec typ #

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

Instances details
(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Entity rec)) (SqlExpr (Value typ))

This instance allows you to use record.field notation with GHC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
BlogPost
    authorId     PersonId
    title        Text

-- query:
select $ do
    bp <- from $ table @BlogPost
    pure $ bp.title

This is exactly equivalent to the following:

blogPost :: SqlExpr (Entity BlogPost)

blogPost ^. BlogPostTitle
blogPost ^. #title
blogPost.title

There's another instance defined on SqlExpr (Entity (Maybe rec)), which allows you to project from a LEFT JOINed entity.

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Entity rec) -> SqlExpr (Value typ) #

(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Maybe (Entity rec))) (SqlExpr (Value (Maybe typ)))

This instance allows you to use record.field notation with GC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
Person
    name         Text

BlogPost
    title        Text
    authorId     PersonId

-- query:

select $ do
    (p :& bp) <- from $
        table Person
        leftJoin table BlogPost
        on do
            \(p :& bp) ->
                just p.id ==. bp.authorId
    pure (p.name, bp.title)

The following forms are all equivalent:

blogPost :: SqlExpr (Maybe (Entity BlogPost))

blogPost ?. BlogPostTitle
blogPost ?. #title
blogPost.title

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Maybe (Entity rec)) -> SqlExpr (Value (Maybe typ)) #

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

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

ToAlias (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a)) #

ToAlias (SqlExpr (Maybe (Entity a))) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Maybe (Entity a)) -> SqlQuery (SqlExpr (Maybe (Entity a))) #

ToAliasReference (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToAliasReference (SqlExpr (Maybe (Entity a))) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToMaybe (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Entity a)) #

Methods

toMaybe :: SqlExpr (Entity a) -> ToMaybeT (SqlExpr (Entity a)) #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

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

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

Defined in Database.Persist.Class.PersistEntity

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

Defined in Database.Persist.Sql.Class

Methods

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

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

Defined in Database.Persist.Sql.Class

Methods

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

rawSqlColCountReason :: Entity record -> String #

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

PersistEntity ent => ToFrom (Table ent) (SqlExpr (Entity ent)) 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: Table ent -> From (SqlExpr (Entity ent)) #

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

You may return an Entity from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

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

You may return a possibly-NULL 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.13.3.5-JQO0xSplhu4Dob8Xs9toj2" '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)))
type ToMaybeT (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

data FilterValue typ where #

Value to filter with. Highly dependant on the type of filter used.

Since: persistent-2.10.0

Constructors

FilterValue :: forall typ. typ -> FilterValue typ 
FilterValues :: forall typ. [typ] -> FilterValue typ 
UnsafeValue :: forall a typ. PersistField a => a -> FilterValue typ 

type family BackendSpecificUpdate backend 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 #

Persistent allows multiple different backends (databases).

data Key record #

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

data EntityField record :: Type -> Type #

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

As of persistent-2.11.0.0, it's possible to use the OverloadedLabels language extension to refer to EntityField values polymorphically. See the documentation on SymbolToField for more information.

data Unique record #

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 :: proxy 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 -> NonEmpty (FieldNameHS, FieldNameDB) #

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.

keyFromRecordM :: Maybe (record -> Key record) #

Extract a Key record from a record value. Currently, this is only defined for entities using the Primary syntax for natural/composite keys. In a future version of persistent which incorporates the ID directly into the entity, this will always be Just.

Since: persistent-2.11.0.0

type family PersistEntityBackend record #

Persistent allows multiple different backends (databases).

data family Key record #

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

Instances

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

Defined in Database.Persist.Sql.Class

data family EntityField record :: Type -> Type #

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

As of persistent-2.11.0.0, it's possible to use the OverloadedLabels language extension to refer to EntityField values polymorphically. See the documentation on SymbolToField for more information.

Instances

Instances details
SymbolToField sym rec typ => IsLabel sym (EntityField rec typ)

This instance delegates to SymbolToField to provide OverloadedLabels support to the EntityField type.

Since: persistent-2.11.0.0

Instance details

Defined in Database.Persist.Class.PersistEntity

Methods

fromLabel :: EntityField rec typ #

data family Unique record #

Unique keys besides the Key.

Instances

Instances details
FinalResult (Unique val) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

finalR :: Unique val -> KnowResult (Unique val) #

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

Get list of values corresponding to given entity.

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

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

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

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

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

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

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

insertMany :: forall record (m :: Type -> Type). (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   |
+-----+------+-----+

repsert :: forall record (m :: Type -> Type). (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 :: forall record (m :: Type -> Type). (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 :: forall record (m :: Type -> Type). (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 :: forall record (m :: Type -> Type). (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 (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 #

Minimal complete definition

get

class PersistCore backend #

Associated Types

data BackendKey backend #

data family BackendKey backend #

Instances

Instances details
newtype BackendKey SqlReadBackend 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

newtype BackendKey SqlWriteBackend 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

newtype BackendKey SqlBackend 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlReadBackend) 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlReadBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.13.3.5-JQO0xSplhu4Dob8Xs9toj2" 'True) (C1 ('MetaCons "SqlReadBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlReadBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))
type Rep (BackendKey SqlWriteBackend) 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlWriteBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.13.3.5-JQO0xSplhu4Dob8Xs9toj2" 'True) (C1 ('MetaCons "SqlWriteBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlWriteBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))
type Rep (BackendKey SqlBackend) 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.13.3.5-JQO0xSplhu4Dob8Xs9toj2" 'True) (C1 ('MetaCons "SqlBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))

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 #

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

A convenient alias for common type signatures

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' = withCompatibleBackend asdf

Since: persistent-2.7.1

Methods

projectBackend :: sub -> sup #

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

Methods

persistBackend :: backend -> BaseBackend backend #

withBaseBackend :: forall backend (m :: Type -> Type) a. HasPersistBackend backend => ReaderT (BaseBackend backend) m a -> ReaderT backend m a #

Run a query against a larger backend by plucking out BaseBackend backend

This is a helper for reusing existing queries when expanding the backend type.

Since: persistent-2.12.0

withCompatibleBackend :: forall sup sub (m :: Type -> Type) a. BackendCompatible sup sub => ReaderT sup m a -> ReaderT sub m a #

Run a query against a compatible backend, by projecting the backend

This is a helper for using queries which run against a specific backend type that your backend is compatible with.

Since: persistent-2.12.0

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

getJust :: forall record backend (m :: Type -> Type). (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 :: forall record backend (m :: Type -> Type). (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

belongsTo :: forall ent1 ent2 backend (m :: Type -> Type). (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 :: forall ent1 ent2 backend (m :: Type -> Type). (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.

insertEntity :: forall e backend (m :: Type -> Type). (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 :: forall record backend (m :: Type -> Type). (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

data SqlBackend #

A SqlBackend represents a handle or connection to a database. It contains functions and values that allow databases to have more optimized implementations, as well as references that benefit performance and sharing.

Instead of using the SqlBackend constructor directly, use the mkSqlBackend function.

A SqlBackend is *not* thread-safe. You should not assume that a SqlBackend can be shared among threads and run concurrent queries. This *will* result in problems. Instead, you should create a Pool SqlBackend, known as a ConnectionPool, and pass that around in multi-threaded applications.

To run actions in the persistent library, you should use the runSqlConn function. If you're using a multithreaded application, use the runSqlPool function.

Instances

Instances details
HasPersistBackend SqlBackend 
Instance details

Defined in Database.Persist.SqlBackend.Internal

Associated Types

type BaseBackend SqlBackend #

IsPersistBackend SqlBackend 
Instance details

Defined in Database.Persist.SqlBackend.Internal

newtype BackendKey SqlBackend 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type BaseBackend SqlBackend 
Instance details

Defined in Database.Persist.SqlBackend.Internal

type Rep (BackendKey SqlBackend) 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.13.3.5-JQO0xSplhu4Dob8Xs9toj2" 'True) (C1 ('MetaCons "SqlBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))

class PersistEntity record => AtLeastOneUniqueKey record where #

This class is used to ensure that functions requring at least one unique key are not called with records that have 0 unique keys. The quasiquoter automatically writes working instances for appropriate entities, and generates TypeError instances for records that have 0 unique keys.

Since: persistent-2.10.0

Methods

requireUniquesP :: record -> NonEmpty (Unique record) #

type MultipleUniqueKeysError ty = ((('Text "The entity " :<>: 'ShowType ty) :<>: 'Text " has multiple unique keys.") :$$: ('Text "The function you are trying to call requires only a single " :<>: 'Text "unique key.")) :$$: (('Text "There is probably a variant of the function with 'By' " :<>: 'Text "appended that will allow you to select a unique key ") :<>: 'Text "for the operation.") #

This is an error message. It is used when an entity has multiple unique keys, and the function expects a single unique key.

Since: persistent-2.10.0

type NoUniqueKeysError ty = (('Text "The entity " :<>: 'ShowType ty) :<>: 'Text " does not have any unique keys.") :$$: ('Text "The function you are trying to call requires a unique key " :<>: 'Text "to be defined on the entity.") #

This is an error message. It is used when writing instances of OnlyOneUniqueKey for an entity that has no unique keys.

Since: persistent-2.10.0

class PersistEntity record => OnlyOneUniqueKey record where #

This class is used to ensure that upsert is only called on records that have a single Unique key. The quasiquoter automatically generates working instances for appropriate records, and generates TypeError instances for records that have 0 or multiple unique keys.

Since: persistent-2.10.0

Methods

onlyUniqueP :: record -> Unique record #

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 :: forall record (m :: Type -> Type). (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 :: forall record (m :: Type -> Type). (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

:: forall record (m :: Type -> Type). (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

:: forall record (m :: Type -> Type). (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

:: forall record (m :: Type -> Type). (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 PersistStoreRead backend => PersistUniqueRead backend #

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.

Minimal complete definition

getBy

onlyOneUniqueDef :: (OnlyOneUniqueKey record, Monad proxy) => proxy record -> UniqueDef #

Given a proxy for a PersistEntity record, this returns the sole UniqueDef for that entity.

Since: persistent-2.13.0.0

insertBy :: forall record backend (m :: Type -> Type). (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 :: forall record backend (m :: Type -> Type). (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 :: forall record backend (m :: Type -> Type). (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.

getByValue :: forall record (m :: Type -> Type) backend. (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 |
+----+------+-----+

replaceUnique :: forall record backend (m :: Type -> Type). (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

checkUnique :: forall record backend (m :: Type -> Type). (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

checkUniqueUpdateable :: forall record backend (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend, PersistUniqueRead backend) => Entity 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 stay unique, and could thus safely be updated. on a conflict returns the conflicting key

This is similar to checkUnique, except it's useful for updating - when the particular entity already exists, it would normally conflict with itself. This variant ignores those conflicts

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

Since: persistent-2.11.0.0

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

Backends supporting conditional write operations

Minimal complete definition

updateWhere, deleteWhere

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

Backends supporting conditional read operations.

Minimal complete definition

selectSourceRes, selectKeysRes, count, exists

Methods

selectSourceRes :: forall record (m1 :: Type -> Type) (m2 :: Type -> Type). (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.

NOTE: This function returns an Acquire and a ConduitM, which implies that it streams from the database. It does not. Please use selectList to simplify the code. If you want streaming behavior, consider persistent-pagination which efficiently chunks a query into ranges, or investigate a backend-specific streaming solution.

selectKeysRes :: forall (m1 :: Type -> Type) (m2 :: Type -> Type) record. (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.

selectKeys :: forall record backend (m :: Type -> Type). (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.

For an example, see selectList.

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 :: forall (m :: Type -> Type). MonadIO m => Key record -> ReaderT backend m () #

Perform cascade-deletion of single database entry.

deleteCascadeWhere :: forall record backend (m :: Type -> Type). (MonadIO m, DeleteCascade record backend, PersistQueryWrite backend) => [Filter record] -> ReaderT backend m () #

Cascade-deletion of entries satisfying given filters.

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.

type IsSqlBackend backend = (IsPersistBackend backend, BaseBackend backend ~ SqlBackend) #

A backend which is a wrapper around SqlBackend.

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.

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

newtype SqlWriteBackend #

An SQL backend which can handle read or write queries

The constructor was exposed in 2.10.0

Instances

Instances details
HasPersistBackend SqlWriteBackend 
Instance details

Defined in Database.Persist.Sql.Types.Internal

Associated Types

type BaseBackend SqlWriteBackend #

IsPersistBackend SqlWriteBackend 
Instance details

Defined in Database.Persist.Sql.Types.Internal

newtype BackendKey SqlWriteBackend 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type BaseBackend SqlWriteBackend 
Instance details

Defined in Database.Persist.Sql.Types.Internal

type Rep (BackendKey SqlWriteBackend) 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlWriteBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.13.3.5-JQO0xSplhu4Dob8Xs9toj2" 'True) (C1 ('MetaCons "SqlWriteBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlWriteBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))

newtype SqlReadBackend #

An SQL backend which can only handle read queries

The constructor was exposed in 2.10.0.

Instances

Instances details
HasPersistBackend SqlReadBackend 
Instance details

Defined in Database.Persist.Sql.Types.Internal

Associated Types

type BaseBackend SqlReadBackend #

IsPersistBackend SqlReadBackend 
Instance details

Defined in Database.Persist.Sql.Types.Internal

newtype BackendKey SqlReadBackend 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type BaseBackend SqlReadBackend 
Instance details

Defined in Database.Persist.Sql.Types.Internal

type Rep (BackendKey SqlReadBackend) 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlReadBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.13.3.5-JQO0xSplhu4Dob8Xs9toj2" 'True) (C1 ('MetaCons "SqlReadBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlReadBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))

writeToUnknown :: forall (m :: Type -> Type) a. Monad m => ReaderT SqlWriteBackend m a -> ReaderT SqlBackend m a #

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

readToWrite :: forall (m :: Type -> Type) a. Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlWriteBackend m a #

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

readToUnknown :: forall (m :: Type -> Type) a. Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlBackend m a #

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

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

Instances details
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 #

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 #

PersistField a => RawSql (Single a) 
Instance details

Defined in Database.Persist.Sql.Class

data ConnectionPoolConfig #

Values to configure a pool of database connections. See Data.Pool for details.

Since: persistent-2.11.0.0

Constructors

ConnectionPoolConfig 

Fields

data ColumnReference #

This value specifies how a field references another table.

Since: persistent-2.11.0.0

Constructors

ColumnReference 

Fields

data Column #

Instances

Instances details
Show Column 
Instance details

Defined in Database.Persist.Sql.Types

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

defaultConnectionPoolConfig :: ConnectionPoolConfig #

Initializes a ConnectionPoolConfig with default values. See the documentation of ConnectionPoolConfig for each field's default value.

Since: persistent-2.11.0.0

data BackendSpecificOverrides #

Record of functions to override the default behavior in mkColumns. It is recommended you initialize this with emptyBackendSpecificOverrides and override the default values, so that as new fields are added, your code still compiles.

For added safety, use the getBackendSpecific* and setBackendSpecific* functions, as a breaking change to the record field labels won't be reflected in a major version bump of the library.

Since: persistent-2.11

getBackendSpecificForeignKeyName :: BackendSpecificOverrides -> Maybe (EntityNameDB -> FieldNameDB -> ConstraintNameDB) #

If the override is defined, then this returns a function that accepts an entity name and field name and provides the ConstraintNameDB for the foreign key constraint.

An abstract accessor for the BackendSpecificOverrides

Since: persistent-2.13.0.0

setBackendSpecificForeignKeyName :: (EntityNameDB -> FieldNameDB -> ConstraintNameDB) -> BackendSpecificOverrides -> BackendSpecificOverrides #

Set the backend's foreign key generation function to this value.

Since: persistent-2.13.0.0

emptyBackendSpecificOverrides :: BackendSpecificOverrides #

Creates an empty BackendSpecificOverrides (i.e. use the default behavior; no overrides)

Since: persistent-2.11

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

Create the list of columns for the given entity.

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

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

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 = PersistLiteralEncoded . toASCIIBytes
  fromPersistValue (PersistLiteralEncoded 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 PersistLiteralEncoded, 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

Instances details
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 Int8 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Int8 -> SqlType #

PersistFieldSql Rational 
Instance details

Defined in Database.Persist.Sql.Class

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 Html 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Html -> SqlType #

PersistFieldSql ByteString 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql OverflowNatural

This type uses the SqlInt64 version, which will exhibit overflow and underflow behavior. Additionally, it permits negative values in the database, which isn't ideal.

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql PersistValue 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql Checkmark 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql Text 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Text -> SqlType #

PersistFieldSql Text 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Text -> SqlType #

PersistFieldSql Day 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Day -> SqlType #

PersistFieldSql UTCTime 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql TimeOfDay 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql Word8 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Word8 -> SqlType #

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 Word 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Word -> 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 #

PersistFieldSql a => PersistFieldSql (Maybe a) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy (Maybe a) -> 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 (Map Text v) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

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

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

Defined in Database.Persist.Sql.Class

Methods

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

newtype EntityWithPrefix (prefix :: Symbol) record #

This newtype wrapper is useful when selecting an entity out of the database and you want to provide a prefix to the table being selected.

Consider this raw SQL query:

SELECT ??
FROM my_long_table_name AS mltn
INNER JOIN other_table AS ot
   ON mltn.some_col = ot.other_col
WHERE ...

We don't want to refer to my_long_table_name every time, so we create an alias. If we want to select it, we have to tell the raw SQL quasi-quoter that we expect the entity to be prefixed with some other name.

We can give the above query a type with this, like:

getStuff :: SqlPersistM [EntityWithPrefix "mltn" MyLongTableName]
getStuff = rawSql queryText []

The EntityWithPrefix bit is a boilerplate newtype wrapper, so you can remove it with unPrefix, like this:

getStuff :: SqlPersistM [Entity MyLongTableName]
getStuff = unPrefix @"mltn" <$> rawSql queryText []

The symbol is a "type application" and requires the TypeApplications@ language extension.

Since: persistent-2.10.5

Constructors

EntityWithPrefix 

Fields

Instances

Instances details
(PersistEntity record, KnownSymbol prefix, PersistEntityBackend record ~ backend, IsPersistBackend backend) => RawSql (EntityWithPrefix prefix record) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> EntityWithPrefix prefix record -> (Int, [Text]) #

rawSqlColCountReason :: EntityWithPrefix prefix record -> String #

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

class RawSql a where #

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

Methods

rawSqlCols :: (Text -> 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

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

Defined in Database.Persist.Sql.Class

Methods

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

rawSqlColCountReason :: Entity record -> String #

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

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

Defined in Database.Persist.Sql.Class

PersistField a => RawSql (Single a) 
Instance details

Defined in Database.Persist.Sql.Class

RawSql a => RawSql (Maybe a)

Since: persistent-1.0.1

Instance details

Defined in Database.Persist.Sql.Class

(PersistEntity record, KnownSymbol prefix, PersistEntityBackend record ~ backend, IsPersistBackend backend) => RawSql (EntityWithPrefix prefix record) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> EntityWithPrefix prefix record -> (Int, [Text]) #

rawSqlColCountReason :: EntityWithPrefix prefix record -> String #

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

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

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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) #

(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 m) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

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

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

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

(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 m, RawSql n) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

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

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

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

(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 m, RawSql n, RawSql o) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

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

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

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

(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 m, RawSql n, RawSql o, RawSql p) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

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

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

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

(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 m, RawSql n, RawSql o, RawSql p, RawSql q) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

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

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> String #

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

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3, RawSql g3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3, RawSql g3, RawSql h3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3, RawSql g3, RawSql h3, RawSql i3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3, RawSql g3, RawSql h3, RawSql i3, RawSql j3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3, j3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3, j3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3, j3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3, j3) #

unPrefix :: forall (prefix :: Symbol) record. EntityWithPrefix prefix record -> Entity record #

A helper function to tell GHC what the EntityWithPrefix prefix should be. This allows you to use a type application to specify the prefix, instead of specifying the etype on the result.

As an example, here's code that uses this:

myQuery :: SqlPersistM [Entity Person]
myQuery = fmap (unPrefix @"p") $ rawSql query []
  where
    query = "SELECT ?? FROM person AS p"

Since: persistent-2.10.5

rawQuery :: forall (m :: Type -> Type) env. (MonadResource m, MonadReader env m, BackendCompatible SqlBackend env) => Text -> [PersistValue] -> ConduitM () [PersistValue] m () #

rawQueryRes :: forall (m1 :: Type -> Type) (m2 :: Type -> Type) env. (MonadIO m1, MonadIO m2, BackendCompatible SqlBackend env) => Text -> [PersistValue] -> ReaderT env m1 (Acquire (ConduitM () [PersistValue] m2 ())) #

rawExecute #

Arguments

:: forall (m :: Type -> Type) backend. (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

:: forall (m :: Type -> Type) backend. (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

:: forall a (m :: Type -> Type) backend. (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)

runSqlPool :: forall backend m a. (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.

This function performs the given action in a transaction. If an exception occurs during the action, then the transaction is rolled back.

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.

runSqlPoolWithIsolation :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> IsolationLevel -> m a #

Like runSqlPool, but supports specifying an isolation level.

Since: persistent-2.9.0

runSqlPoolNoTransaction :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> Maybe IsolationLevel -> m a #

Like runSqlPool, but does not surround the action in a transaction. This action might leave your database in a weird state.

Since: persistent-2.12.0.0

runSqlPoolWithHooks #

Arguments

:: forall backend m a before after onException. (MonadUnliftIO m, BackendCompatible SqlBackend backend) 
=> ReaderT backend m a 
-> Pool backend 
-> Maybe IsolationLevel 
-> (backend -> m before)

Run this action immediately before the action is performed.

-> (backend -> m after)

Run this action immediately after the action is completed.

-> (backend -> SomeException -> m onException)

This action is performed when an exception is received. The exception is provided as a convenience - it is rethrown once this cleanup function is complete.

-> m a 

This function is how runSqlPool and runSqlPoolNoTransaction are defined. In addition to the action to be performed and the Pool of conections to use, we give you the opportunity to provide three actions - initialize, afterwards, and onException.

Since: persistent-2.12.0.0

runSqlPoolWithExtensibleHooks :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> Maybe IsolationLevel -> SqlPoolHooks m backend -> m a #

This function is how runSqlPoolWithHooks is defined.

It's currently the most general function for using a SQL pool.

Since: persistent-2.13.0.0

acquireSqlConn :: (MonadReader backend m, BackendCompatible SqlBackend backend) => m (Acquire backend) #

Starts a new transaction on the connection. When the acquired connection is released the transaction is committed and the connection returned to the pool.

Upon an exception the transaction is rolled back and the connection destroyed.

This is equivalent to runSqlConn but does not incur the MonadUnliftIO constraint, meaning it can be used within, for example, a Conduit pipeline.

Since: persistent-2.10.5

acquireSqlConnWithIsolation :: (MonadReader backend m, BackendCompatible SqlBackend backend) => IsolationLevel -> m (Acquire backend) #

Like acquireSqlConn, but lets you specify an explicit isolation level.

Since: persistent-2.10.5

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

runSqlConnWithIsolation :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> backend -> IsolationLevel -> m a #

Like runSqlConn, but supports specifying an isolation level.

Since: persistent-2.9.0

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

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

withSqlPool #

Arguments

:: forall backend m a. (MonadLoggerIO m, MonadUnliftIO m, BackendCompatible SqlBackend backend) 
=> (LogFunc -> IO backend)

create a new connection

-> Int

connection count

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

withSqlPoolWithConfig #

Arguments

:: forall backend m a. (MonadLoggerIO m, MonadUnliftIO m, BackendCompatible SqlBackend backend) 
=> (LogFunc -> IO backend)

Function to create a new connection

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

Creates a pool of connections to a SQL database which can be used by the Pool backend -> m a function. After the function completes, the connections are destroyed.

Since: persistent-2.11.0.0

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

createSqlPoolWithConfig #

Arguments

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

Function to create a new connection

-> ConnectionPoolConfig 
-> m (Pool backend) 

Creates a pool of connections to a SQL database.

Since: persistent-2.11.0.0

withSqlConn :: forall backend m a. (MonadUnliftIO m, MonadLoggerIO 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}}]

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

withRawQuery :: forall (m :: Type -> Type) a. MonadIO m => Text -> [PersistValue] -> ConduitM [PersistValue] Void IO a -> ReaderT SqlBackend m a #

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

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

getTableName :: forall record (m :: Type -> Type) backend. (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 -> EntityNameDB #

useful for a backend to implement tableName by adding escaping

getFieldName :: forall record typ (m :: Type -> Type) backend. (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

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

useful for a backend to implement fieldName by adding escaping

data FilterTablePrefix #

Used when determining how to prefix a column name in a WHERE clause.

Since: persistent-2.12.1.0

Constructors

PrefixTableName

Prefix the column with the table name. This is useful if the column name might be ambiguous.

Since: persistent-2.12.1.0

PrefixExcluded

Prefix the column name with the EXCLUDED keyword. This is used with the Postgresql backend when doing ON CONFLICT DO UPDATE clauses - see the documentation on upsertWhere and upsertManyWhere.

Since: persistent-2.12.1.0

filterClause #

Arguments

:: PersistEntity val 
=> Maybe FilterTablePrefix

include table name or EXCLUDED

-> SqlBackend 
-> [Filter val] 
-> Text 

Render a [Filter record] into a Text value suitable for inclusion into a SQL query.

Since: persistent-2.12.1.0

filterClauseWithVals #

Arguments

:: PersistEntity val 
=> Maybe FilterTablePrefix

include table name or EXCLUDED

-> SqlBackend 
-> [Filter val] 
-> (Text, [PersistValue]) 

Render a [Filter record] into a Text value suitable for inclusion into a SQL query, as well as the [PersistValue] to properly fill in the ? place holders.

Since: persistent-2.12.1.0

orderClause #

Arguments

:: PersistEntity val 
=> Maybe FilterTablePrefix

include table name or EXCLUDED

-> SqlBackend 
-> [SelectOpt val] 
-> Text 

Render a [SelectOpt record] made up *only* of Asc and Desc constructors into a Text value suitable for inclusion into a SQL query.

Since: persistent-2.13.2.0

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

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

newtype PersistUnsafeMigrationException #

An exception indicating that Persistent refused to run some unsafe migrations. Contains a list of pairs where the Bool tracks whether the migration was unsafe (True means unsafe), and the Sql is the sql statement for the migration.

Since: persistent-2.11.1.0

Instances

Instances details
Exception PersistUnsafeMigrationException 
Instance details

Defined in Database.Persist.Sql.Migration

Show PersistUnsafeMigrationException

This Show instance renders an error message suitable for printing to the console. This is a little dodgy, but since GHC uses Show instances when displaying uncaught exceptions, we have little choice.

Instance details

Defined in Database.Persist.Sql.Migration

type Migration = WriterT [Text] (WriterT CautiousMigration (ReaderT SqlBackend IO)) () #

A Migration is a four level monad stack consisting of:

type CautiousMigration = [(Bool, Sql)] #

A list of SQL operations, marked with a safety flag. If the Bool is True, then the operation is *unsafe* - it might be destructive, or otherwise not idempotent. If the Bool is False, then the operation is *safe*, and can be run repeatedly without issues.

type Sql = Text #

parseMigration :: forall (m :: Type -> Type). (HasCallStack, 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' :: forall (m :: Type -> Type). (HasCallStack, 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 :: forall (m :: Type -> Type). (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m () #

Prints a migration.

showMigration :: forall (m :: Type -> Type). (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m [Text] #

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

getMigration :: forall (m :: Type -> Type). (MonadIO m, HasCallStack) => 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.

runMigration :: forall (m :: Type -> Type). 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 throws a PersistUnsafeMigrationException.

runMigrationQuiet :: forall (m :: Type -> Type). MonadIO m => Migration -> ReaderT SqlBackend m [Text] #

Same as runMigration, but does not report the individual migrations on stderr. Instead it returns a list of the executed SQL commands.

This is a safer/more robust alternative to runMigrationSilent, but may be less silent for some persistent implementations, most notably persistent-postgresql

Since: persistent-2.10.2

runMigrationSilent :: forall (m :: Type -> Type). 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 :: forall (m :: Type -> Type). MonadIO m => Migration -> ReaderT SqlBackend m () #

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

runMigrationUnsafeQuiet :: forall (m :: Type -> Type). (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m [Text] #

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

Since: persistent-2.10.2

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.

reportError :: Text -> Migration #

Report a single error in a Migration.

Since: persistent-2.9.2

reportErrors :: [Text] -> Migration #

Report multiple errors in a Migration.

Since: persistent-2.9.2

addMigration #

Arguments

:: Bool

Is the migration unsafe to run? (eg a destructive or non-idempotent update on the schema). If True, the migration is *unsafe*, and will need to be run manually later. If False, the migration is *safe*, and can be run any number of times.

-> Sql

A Text value representing the command to run on the database.

-> Migration 

Add a migration to the migration plan.

Since: persistent-2.9.2

addMigrations :: CautiousMigration -> Migration #

Add a CautiousMigration (aka a [(Bool, Text)]) to the migration plan.

Since: persistent-2.9.2

runSqlCommand :: SqlPersistT IO () -> Migration #

Run an action against the database during a migration. Can be useful for eg creating Postgres extensions:

runSqlCommand $ rawExecute "CREATE EXTENSION IF NOT EXISTS "uuid-ossp";" []

Since: persistent-2.13.0.0

transactionSave :: forall (m :: Type -> Type). 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

transactionSaveWithIsolation :: forall (m :: Type -> Type). MonadIO m => IsolationLevel -> ReaderT SqlBackend m () #

Commit the current transaction and begin a new one with the specified isolation level.

Since: persistent-2.9.0

transactionUndo :: forall (m :: Type -> Type). 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

transactionUndoWithIsolation :: forall (m :: Type -> Type). MonadIO m => IsolationLevel -> ReaderT SqlBackend m () #

Roll back the current transaction and begin a new one with the specified isolation level.

Since: persistent-2.9.0

deleteWhere :: (PersistRecordBackend record SqlBackend, Typeable record, MonadSqlQuery m) => [Filter record] -> m () #

The lifted version of deleteWhere

updateWhere :: (PersistRecordBackend record SqlBackend, Typeable record, MonadSqlQuery m) => [Filter record] -> [Update record] -> m () #

The lifted version of updateWhere

selectFirst :: (PersistRecordBackend record SqlBackend, Typeable record, MonadSqlQuery m) => [Filter record] -> [SelectOpt record] -> m (Maybe (Entity record)) #

The lifted version of selectFirst

getBy :: (PersistRecordBackend record SqlBackend, Typeable record, MonadSqlQuery m) => Unique record -> m (Maybe (Entity record)) #

The lifted version of getBy

insertKey :: (PersistRecordBackend record SqlBackend, Typeable record, MonadSqlQuery m) => Key record -> record -> m () #

The lifted version of insertKey

insertEntityMany :: (PersistRecordBackend record SqlBackend, Typeable record, MonadSqlQuery m) => [Entity record] -> m () #

The lifted version of insertEntityMany

insertMany_ :: (PersistRecordBackend record SqlBackend, Typeable record, MonadSqlQuery m) => [record] -> m () #

The lifted version of insertMany_

insert_ :: (PersistRecordBackend record SqlBackend, Typeable record, MonadSqlQuery m) => record -> m () #

The lifted version of insert_

insert :: (PersistRecordBackend record SqlBackend, Typeable record, MonadSqlQuery m) => record -> m (Key record) #

The lifted version of insert

getEntity :: (PersistRecordBackend record SqlBackend, Typeable record, MonadSqlQuery m) => Key record -> m (Maybe (Entity record)) #

The lifted version of getEntity

getMany :: (PersistRecordBackend record SqlBackend, Typeable record, MonadSqlQuery m) => [Key record] -> m (Map (Key record) record) #

The lifted version of getMany

get :: (PersistRecordBackend record SqlBackend, Typeable record, MonadSqlQuery m) => Key record -> m (Maybe record) #

The lifted version of get

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

Classy version of select

selectOne :: (MonadSqlQuery m, SqlSelect a r) => SqlQuery a -> m (Maybe r) Source #

Classy version of selectOne

delete :: MonadSqlQuery m => SqlQuery () -> m () Source #

Classy version of delete

withRecursive :: (ToAlias a, ToAliasReference a, SqlSelect a r) => SqlQuery a -> UnionKind -> (From a -> SqlQuery a) -> SqlQuery (From a) #

WITH RECURSIVE allows one to make a recursive subquery, which can reference itself. Like WITH, this is supported in most modern SQL engines. Useful for hierarchical, self-referential data, like a tree of data.

select $ do
cte <- withRecursive
         (do
             person <- from $ table @Person
             where_ $ person ^. PersonId ==. val personId
             pure person
         )
         unionAll_
         (\self -> do
             (p :& f :& p2 :& pSelf) <- from self
                      `innerJoin` $ table @Follow
                      `on` (\(p :& f) ->
                              p ^. PersonId ==. f ^. FollowFollower)
                      `innerJoin` $ table @Person
                      `on` (\(p :& f :& p2) ->
                              f ^. FollowFollowed ==. p2 ^. PersonId)
                      `leftJoin` self
                      `on` (\(_ :& _ :& p2 :& pSelf) ->
                              just (p2 ^. PersonId) ==. pSelf ?. PersonId)
             where_ $ isNothing (pSelf ?. PersonId)
             groupBy (p2 ^. PersonId)
             pure p2
         )
from cte

Since: 3.4.0.0

with :: (ToAlias a, ToAliasReference a, SqlSelect a r) => SqlQuery a -> SqlQuery (From a) #

WITH clause used to introduce a Common Table Expression (CTE). CTEs are supported in most modern SQL engines and can be useful in performance tuning. In Esqueleto, CTEs should be used as a subquery memoization tactic. When writing plain SQL, CTEs are sometimes used to organize the SQL code, in Esqueleto, this is better achieved through function that return SqlQuery values.

select $ do
cte <- with subQuery
cteResult <- from cte
where_ $ cteResult ...
pure cteResult

WARNING: In some SQL engines using a CTE can diminish performance. In these engines the CTE is treated as an optimization fence. You should always verify that using a CTE will in fact improve your performance over a regular subquery.

Notably, in PostgreSQL prior to version 12, CTEs are always fully calculated, which can potentially significantly pessimize queries. As of PostgreSQL 12, non-recursive and side-effect-free queries may be inlined and optimized accordingly if not declared MATERIALIZED to get the previous behaviour. See the PostgreSQL CTE documentation, section Materialization, for more information.

Since: 3.4.0.0

fullOuterJoin :: (ToFrom a a', ToFrom b b', ToMaybe a', ToMaybe b', HasOnClause rhs (ToMaybeT a' :& ToMaybeT b'), rhs ~ (b, (ToMaybeT a' :& ToMaybeT b') -> SqlExpr (Value Bool))) => a -> rhs -> From (ToMaybeT a' :& ToMaybeT b') infixl 2 #

FULL OUTER JOIN

Join where both sides of the join may not exist. Because of this the result needs to be handled as a Maybe

Used as an infix operator `fullOuterJoin`

select $
from $ table @Person
`fullOuterJoin` table @BlogPost
`on` (\(p :& bp) ->
        p ?. PersonId ==. bp ?. BlogPostAuthorId)

Since: esqueleto-3.5.0.0

rightJoin :: (ToFrom a a', ToFrom b b', ToMaybe a', HasOnClause rhs (ToMaybeT a' :& b'), rhs ~ (b, (ToMaybeT a' :& b') -> SqlExpr (Value Bool))) => a -> rhs -> From (ToMaybeT a' :& b') infixl 2 #

RIGHT OUTER JOIN

Join where the left side may not exist. If the on clause fails then the left side will be NULL'ed Because of this the left side needs to be handled as a Maybe

Used as an infix operator `rightJoin`

select $
from $ table @Person
`rightJoin` table @BlogPost
`on` (\(p :& bp) ->
        p ?. PersonId ==. bp ^. BlogPostAuthorId)

Since: esqueleto-3.5.0.0

leftJoinLateral :: (ToFrom a a', SqlSelect b r, HasOnClause rhs (a' :& ToMaybeT b), ToAlias b, ToAliasReference b, ToMaybe b, rhs ~ (a' -> SqlQuery b, (a' :& ToMaybeT b) -> SqlExpr (Value Bool))) => a -> rhs -> From (a' :& ToMaybeT b) infixl 2 #

LEFT OUTER JOIN LATERAL

Lateral join where the right side may not exist. In the case that the query returns nothing or the on clause fails the right side of the join will be NULL'ed Because of this the right side needs to be handled as a Maybe

Used as an infix operator `leftJoinLateral`

See example 6 for how to use LATERAL

Since: esqueleto-3.5.0.0

leftJoin :: (ToFrom a a', ToFrom b b', ToMaybe b', HasOnClause rhs (a' :& ToMaybeT b'), rhs ~ (b, (a' :& ToMaybeT b') -> SqlExpr (Value Bool))) => a -> rhs -> From (a' :& ToMaybeT b') infixl 2 #

LEFT OUTER JOIN

Join where the right side may not exist. If the on clause fails then the right side will be NULL'ed Because of this the right side needs to be handled as a Maybe

Used as an infix operator `leftJoin`

select $
from $ table @Person
`leftJoin` table @BlogPost
`on` (\(p :& bp) ->
        p ^. PersonId ==. bp ?. BlogPostAuthorId)

Since: esqueleto-3.5.0.0

crossJoinLateral :: (ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b) => a -> (a' -> SqlQuery b) -> From (a' :& b) infixl 2 #

CROSS JOIN LATERAL

A Lateral subquery join allows the joined query to reference entities from the left hand side of the join.

Used as an infix operator `crossJoinLateral`

See example 6

Since: esqueleto-3.5.0.0

crossJoin :: (ToFrom a a', ToFrom b b') => a -> b -> From (a' :& b') infixl 2 #

CROSS JOIN

Used as an infix `crossJoin`

select $ do
from $ table @Person
`crossJoin` table @BlogPost

Since: esqueleto-3.5.0.0

innerJoinLateral :: (ToFrom a a', HasOnClause rhs (a' :& b), SqlSelect b r, ToAlias b, ToAliasReference b, rhs ~ (a' -> SqlQuery b, (a' :& b) -> SqlExpr (Value Bool))) => a -> rhs -> From (a' :& b) infixl 2 #

INNER JOIN LATERAL

A Lateral subquery join allows the joined query to reference entities from the left hand side of the join. Discards rows that don't match the on clause

Used as an infix operator `innerJoinLateral`

See example 6

Since: esqueleto-3.5.0.0

innerJoin :: (ToFrom a a', ToFrom b b', HasOnClause rhs (a' :& b'), rhs ~ (b, (a' :& b') -> SqlExpr (Value Bool))) => a -> rhs -> From (a' :& b') infixl 2 #

INNER JOIN

Used as an infix operator `innerJoin`

select $
from $ table @Person
`innerJoin` table @BlogPost
`on` (\(p :& bp) ->
        p ^. PersonId ==. bp ^. BlogPostAuthorId)

Since: esqueleto-3.5.0.0

on :: ValidOnClause a => a -> (b -> SqlExpr (Value Bool)) -> (a, b -> SqlExpr (Value Bool)) infix 9 #

An ON clause that describes how two tables are related. This should be used as an infix operator after a JOIN. For example,

select $
from $ table @Person
`innerJoin` table @BlogPost
`on` (\(p :& bP) ->
        p ^. PersonId ==. bP ^. BlogPostAuthorId)

data a :& b infixl 2 #

A left-precedence pair. Pronounced "and". Used to represent expressions that have been joined together.

The precedence behavior can be demonstrated by:

a :& b :& c == ((a :& b) :& c)

See the examples at the beginning of this module to see how this operator is used in JOIN operations.

Constructors

a :& b infixl 2 

Instances

Instances details
(ToFrom a a', ToFrom b b') => DoCrossJoin NotLateral a b (a' :& b') 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doCrossJoin :: Proxy NotLateral -> a -> b -> From (a' :& b') #

(ToFrom a a', ToFrom b b', HasOnClause rhs (a' :& b'), rhs ~ (b, (a' :& b') -> SqlExpr (Value Bool))) => DoInnerJoin NotLateral a rhs (a' :& b') 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doInnerJoin :: Proxy NotLateral -> a -> rhs -> From (a' :& b') #

(ToFrom a a', ToFrom b b', ToMaybe b', ToMaybeT b' ~ mb, HasOnClause rhs (a' :& mb), rhs ~ (b, (a' :& mb) -> SqlExpr (Value Bool))) => DoLeftJoin NotLateral a rhs (a' :& mb) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doLeftJoin :: Proxy NotLateral -> a -> rhs -> From (a' :& mb) #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b) => DoCrossJoin Lateral a (a' -> SqlQuery b) (a' :& b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doCrossJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b) -> From (a' :& b) #

(Show a, Show b) => Show (a :& b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

showsPrec :: Int -> (a :& b) -> ShowS #

show :: (a :& b) -> String #

showList :: [a :& b] -> ShowS #

(ToAlias a, ToAlias b) => ToAlias (a :& b)

Identical to the tuple instance and provided for convenience.

Since: esqueleto-3.5.3.0

Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

(ToAliasReference a, ToAliasReference b) => ToAliasReference (a :& b)

Identical to the tuple instance and provided for convenience.

Since: esqueleto-3.5.3.0

Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toAliasReference :: Ident -> (a :& b) -> SqlQuery (a :& b) #

(ToMaybe a, ToMaybe b) => ToMaybe (a :& b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Associated Types

type ToMaybeT (a :& b) #

Methods

toMaybe :: (a :& b) -> ToMaybeT (a :& b) #

(Eq a, Eq b) => Eq (a :& b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

(==) :: (a :& b) -> (a :& b) -> Bool #

(/=) :: (a :& b) -> (a :& b) -> Bool #

(SqlSelect a ra, SqlSelect b rb) => SqlSelect (a :& b) (ra :& rb)

You may return joined values from a select query - this is identical to the tuple instance, but is provided for convenience.

Since: esqueleto-3.5.2.0

Instance details

Defined in Database.Esqueleto.Experimental.From.Join

type ToMaybeT (a :& b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

type ToMaybeT (a :& b) = ToMaybeT a :& ToMaybeT b

intersect_ :: (ToSqlSetOperation a a', ToSqlSetOperation b a') => a -> b -> SqlSetOperation a' #

INTERSECT SQL set operation. Can be used as an infix function between SqlQuery values.

except_ :: (ToSqlSetOperation a a', ToSqlSetOperation b a') => a -> b -> SqlSetOperation a' #

EXCEPT SQL set operation. Can be used as an infix function between SqlQuery values.

pattern SelectQuery :: p -> p #

class ToSqlSetOperation a r | a -> r where #

Type class to support direct use of SqlQuery in a set operation tree

Since: esqueleto-3.5.0.0

data Union a b #

Constructors

a `Union` b 

Instances

Instances details
ToSqlSetOperation a a' => ToSqlSetOperation (Union a a) a' 
Instance details

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

union_ :: Union_ a => a #

UNION SQL set operation. Can be used as an infix function between SqlQuery values.

unionAll_ :: UnionAll_ a => a #

UNION ALL SQL set operation. Can be used as an infix function between SqlQuery values.

data UnionAll a b #

Constructors

a `UnionAll` b 

Instances

Instances details
ToSqlSetOperation a a' => ToSqlSetOperation (UnionAll a a) a' 
Instance details

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

data Except a b #

Constructors

a `Except` b 

Instances

Instances details
ToSqlSetOperation a a' => ToSqlSetOperation (Except a a) a' 
Instance details

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

data Intersect a b #

Constructors

a `Intersect` b 

Instances

Instances details
ToSqlSetOperation a a' => ToSqlSetOperation (Intersect a a) a' 
Instance details

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

selectQuery :: (SqlSelect a r, ToAlias a, ToAliasReference a) => SqlQuery a -> From a #

Select from a subquery, often used in conjuction with joins but can be used without any joins. Because SqlQuery has a ToFrom instance you probably dont need to use this function directly.

select $
     p <- from $
             selectQuery do
             p <- from $ table @Person
             limit 5
             orderBy [ asc p ^. PersonAge ]
     ...

Since: esqueleto-3.5.0.0

table :: PersistEntity ent => From (SqlExpr (Entity ent)) #

Bring a PersistEntity into scope from a table

select $ from $ table @People

Since: esqueleto-3.5.0.0

from :: ToFrom a a' => a -> SqlQuery a' #

FROM clause, used to bring entities into scope.

Internally, this function uses the From datatype. Unlike the old from, this does not take a function as a parameter, but rather a value that represents a JOIN tree constructed out of instances of From. This implementation eliminates certain types of runtime errors by preventing the construction of invalid SQL (e.g. illegal nested-from).

newtype From a #

Data type defining the From language. This should not constructed directly in application code.

A From is a SqlQuery which returns a reference to the result of calling from and a function that produces a portion of a FROM clause. This gets passed to the FromRaw FromClause constructor directly when converting from a From to a SqlQuery using from

Since: esqueleto-3.5.0.0

Constructors

From 

Fields

Instances

Instances details
ToFrom (From a) a 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: From a -> From a #

data Table a #

Constructors

Table 

Instances

Instances details
PersistEntity ent => ToFrom (Table ent) (SqlExpr (Entity ent)) 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: Table ent -> From (SqlExpr (Entity ent)) #

newtype SubQuery a #

Constructors

SubQuery a 

Instances

Instances details
(SqlSelect a r, ToAlias a, ToAliasReference a) => ToFrom (SubQuery (SqlQuery a)) a 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: SubQuery (SqlQuery a) -> From a #

type ToAliasT a = a #

class ToAlias a where #

Methods

toAlias :: a -> SqlQuery a #

Instances

Instances details
ToAlias (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a)) #

ToAlias (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a)) #

ToAlias (SqlExpr (Maybe (Entity a))) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Maybe (Entity a)) -> SqlQuery (SqlExpr (Maybe (Entity a))) #

(ToAlias a, ToAlias b) => ToAlias (a :& b)

Identical to the tuple instance and provided for convenience.

Since: esqueleto-3.5.3.0

Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c) -> SqlQuery (a, b, c) #

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

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d) -> SqlQuery (a, b, c, d) #

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

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e) -> SqlQuery (a, b, c, d, e) #

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

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e, f) -> SqlQuery (a, b, c, d, e, f) #

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

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e, f, g) -> SqlQuery (a, b, c, d, e, f, g) #

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

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e, f, g, h) -> SqlQuery (a, b, c, d, e, f, g, h) #

type ToAliasReferenceT a = a #

class ToAliasReference a where #

Methods

toAliasReference :: Ident -> a -> SqlQuery a #

Instances

Instances details
ToAliasReference (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToAliasReference (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToAliasReference (SqlExpr (Maybe (Entity a))) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

(ToAliasReference a, ToAliasReference b) => ToAliasReference (a :& b)

Identical to the tuple instance and provided for convenience.

Since: esqueleto-3.5.3.0

Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toAliasReference :: Ident -> (a :& b) -> SqlQuery (a :& b) #

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b) -> SqlQuery (a, b) #

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c) -> SqlQuery (a, b, c) #

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d) -> SqlQuery (a, b, c, d) #

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e) -> SqlQuery (a, b, c, d, e) #

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e, f) -> SqlQuery (a, b, c, d, e, f) #

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e, f, g) -> SqlQuery (a, b, c, d, e, f, g) #

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e, f, g, h) -> SqlQuery (a, b, c, d, e, f, g, h) #

type family ToMaybeT a #

Instances

Instances details
type ToMaybeT (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (SqlExpr (Maybe a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a :& b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

type ToMaybeT (a :& b) = ToMaybeT a :& ToMaybeT b
type ToMaybeT (a, b) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a, b) = (ToMaybeT a, ToMaybeT b)
type ToMaybeT (a, b, c) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a, b, c) = (ToMaybeT a, ToMaybeT b, ToMaybeT c)
type ToMaybeT (a, b, c, d) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a, b, c, d) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d)
type ToMaybeT (a, b, c, d, e) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a, b, c, d, e) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e)
type ToMaybeT (a, b, c, d, e, f) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a, b, c, d, e, f) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f)
type ToMaybeT (a, b, c, d, e, f, g) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a, b, c, d, e, f, g) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f, ToMaybeT g)
type ToMaybeT (a, b, c, d, e, f, g, h) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a, b, c, d, e, f, g, h) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f, ToMaybeT g, ToMaybeT h)

class ToMaybe a where #

Associated Types

type ToMaybeT a #

Methods

toMaybe :: a -> ToMaybeT a #

Instances

Instances details
ToMaybe (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Value a)) #

Methods

toMaybe :: SqlExpr (Value a) -> ToMaybeT (SqlExpr (Value a)) #

ToMaybe (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Entity a)) #

Methods

toMaybe :: SqlExpr (Entity a) -> ToMaybeT (SqlExpr (Entity a)) #

ToMaybe (SqlExpr (Maybe a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Maybe a)) #

Methods

toMaybe :: SqlExpr (Maybe a) -> ToMaybeT (SqlExpr (Maybe a)) #

(ToMaybe a, ToMaybe b) => ToMaybe (a :& b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Associated Types

type ToMaybeT (a :& b) #

Methods

toMaybe :: (a :& b) -> ToMaybeT (a :& b) #

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

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b) #

Methods

toMaybe :: (a, b) -> ToMaybeT (a, b) #

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

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b, c) #

Methods

toMaybe :: (a, b, c) -> ToMaybeT (a, b, c) #

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

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b, c, d) #

Methods

toMaybe :: (a, b, c, d) -> ToMaybeT (a, b, c, d) #

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

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b, c, d, e) #

Methods

toMaybe :: (a, b, c, d, e) -> ToMaybeT (a, b, c, d, e) #

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

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b, c, d, e, f) #

Methods

toMaybe :: (a, b, c, d, e, f) -> ToMaybeT (a, b, c, d, e, f) #

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

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b, c, d, e, f, g) #

Methods

toMaybe :: (a, b, c, d, e, f, g) -> ToMaybeT (a, b, c, d, e, f, g) #

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

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b, c, d, e, f, g, h) #

Methods

toMaybe :: (a, b, c, d, e, f, g, h) -> ToMaybeT (a, b, c, d, e, f, g, h) #

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

Avoid N+1 queries and join entities into a map structure.

This function is useful to call on the result of a single JOIN. For example, suppose you have this query:

getFoosAndNestedBarsFromParent
    :: ParentId
    -> SqlPersistT IO [(Entity Foo, Maybe (Entity Bar))]
getFoosAndNestedBarsFromParent parentId =
    select $ do
        (foo :& bar) <- from $
            table Foo
            `LeftOuterJoin`
            table Bar
                `on` do
                    \(foo :& bar) ->
                        foo ^. FooId ==. bar ?. BarFooId
        where_ $
            foo ^. FooParentId ==. val parentId
        pure (foo, bar)

This is a natural result type for SQL - a list of tuples. However, it's not what we usually want in Haskell - each Foo in the list will be represented multiple times, once for each Bar.

We can write fmap associateJoin and it will translate it into a Map that is keyed on the Key of the left Entity, and the value is a tuple of the entity's value as well as the list of each coresponding entity.

getFoosAndNestedBarsFromParentHaskellese
    :: ParentId
    -> SqlPersistT (Map (Key Foo) (Foo, [Maybe (Entity Bar)]))
getFoosAndNestedBarsFromParentHaskellese parentId =
    fmap associateJoin $ getFoosdAndNestedBarsFromParent parentId

What if you have multiple joins?

Let's use associateJoin with a *two* join query.

userPostComments
    :: SqlQuery (SqlExpr (Entity User, Entity Post, Entity Comment))
userPostsComment = do
    (u :& p :& c) <- from $
        table User
        `InnerJoin`
        table Post
            on do
                \(u :& p) ->
                    u ^. UserId ==. p ^. PostUserId
        `InnerJoin`
        table @Comment
            `on` do
                \(_ :& p :& c) ->
                    p ^. PostId ==. c ^. CommentPostId
    pure (u, p, c)

This query returns a User, with all of the users Posts, and then all of the Comments on that post.

First, we *nest* the tuple.

nest :: (a, b, c) -> (a, (b, c))
nest (a, b, c) = (a, (b, c))

This makes the return of the query conform to the input expected from associateJoin.

nestedUserPostComments
    :: SqlPersistT IO [(Entity User, (Entity Post, Entity Comment))]
nestedUserPostComments =
    fmap nest $ select userPostsComments

Now, we can call associateJoin on it.

associateUsers
    :: [(Entity User, (Entity Post, Entity Comment))]
    -> Map UserId (User, [(Entity Post, Entity Comment)])
associateUsers =
    associateJoin

Next, we'll use the Functor instances for Map and tuple to call associateJoin on the [(Entity Post, Entity Comment)].

associatePostsAndComments
    :: Map UserId (User, [(Entity Post, Entity Comment)])
    -> Map UserId (User, Map PostId (Post, [Entity Comment]))
associatePostsAndComments =
    fmap (fmap associateJoin)

For more reading on this topic, see this Foxhound Systems blog post.

Since: esqueleto-3.1.2

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

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

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

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: esqueleto-1.4.2

insertSelectCount :: forall (m :: Type -> Type) a backend. (MonadIO m, PersistEntity a, SqlBackendCanWrite backend) => SqlQuery (SqlExpr (Insertion a)) -> ReaderT backend m Int64 #

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

insertSelect :: forall (m :: Type -> Type) a backend. (MonadIO m, PersistEntity a, SqlBackendCanWrite backend) => SqlQuery (SqlExpr (Insertion a)) -> ReaderT backend m () #

Insert a PersistField for every selected value.

Since: esqueleto-2.4.2

renderQueryInsertInto #

Arguments

:: forall a r backend (m :: Type -> Type). (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.

Since: esqueleto-3.1.1

renderQueryUpdate #

Arguments

:: forall a r backend (m :: Type -> Type). (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.

Since: esqueleto-3.1.1

renderQueryDelete #

Arguments

:: forall a r backend (m :: Type -> Type). (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.

Since: esqueleto-3.1.1

renderQueryToText #

Arguments

:: forall a r backend (m :: Type -> Type). (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: esqueleto-3.1.1

updateCount :: forall (m :: Type -> Type) val backend. (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val), SqlBackendCanWrite backend) => (SqlExpr (Entity val) -> SqlQuery ()) -> ReaderT backend m Int64 #

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

deleteCount :: forall (m :: Type -> Type) backend. (MonadIO m, SqlBackendCanWrite backend) => SqlQuery () -> ReaderT backend m Int64 #

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

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

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

else_ :: expr a -> expr a #

Syntax sugar for case_.

Since: esqueleto-2.1.2

then_ :: () #

Syntax sugar for case_.

Since: esqueleto-2.1.2

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

Syntax sugar for case_.

Since: esqueleto-2.1.2

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

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

In this example, Bar is said to be the BaseEnt(ity), and Foo the child. To model this in Esqueleto, declare:

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

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: esqueleto-2.4.3

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

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: esqueleto-2.1.2

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

Apply extra SqlExpr Value arguments to a PersistField constructor

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

Apply a PersistField constructor to SqlExpr Value arguments.

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

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

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

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

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

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

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.

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

NOT EXISTS operator.

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

EXISTS operator. For example:

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

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

NOT IN operator.

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

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

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

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: esqueleto-2.2.12

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

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

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

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

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

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.

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

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

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

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

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

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" ++. (%)

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

ILIKE operator (case-insensitive LIKE).

Supported by PostgreSQL only.

Since: esqueleto-2.2.3

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

LIKE operator.

right_ :: (SqlString s, Num a) => (SqlExpr (Value s), SqlExpr (Value a)) -> SqlExpr (Value s) #

RIGHT function. @since 3.3.0

left_ :: (SqlString s, Num a) => (SqlExpr (Value s), SqlExpr (Value a)) -> SqlExpr (Value s) #

LEFT function. @since 3.3.0

length_ :: (SqlString s, Num a) => SqlExpr (Value s) -> SqlExpr (Value a) #

LENGTH function. @since 3.3.0

ltrim_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) #

LTRIM function. @since 3.3.0

rtrim_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) #

RTRIM function. @since 3.3.0

trim_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) #

TRIM function. @since 3.3.0

upper_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) #

UPPER function. @since 3.3.0

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

LOWER function.

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

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

Since: esqueleto-1.4.3

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

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: esqueleto-1.4.3

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

Same as castNum, but for nullable values.

Since: esqueleto-2.2.9

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

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: esqueleto-2.2.9

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

BETWEEN.

@since: 3.1.0

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

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

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

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

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

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

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

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

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

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

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

COUNT(DISTINCT x).

Since: esqueleto-2.4.1

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

COUNT.

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

COUNT(*) value.

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

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

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

NULL value.

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

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

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

IS NULL comparison.

For IS NOT NULL, you can negate this with not_, as in not_ (isNothing (person ^. PersonAge))

Warning: Persistent and Esqueleto have different behavior for != Nothing:

HaskellSQL
Persistent!=. NothingIS NOT NULL
Esqueleto!=. Nothing!= NULL

In SQL, = NULL and != NULL return NULL instead of true or false. For this reason, you very likely do not want to use !=. Nothing in Esqueleto. You may find these hlint rules helpful to enforce this:

- error: {lhs: v Database.Esqueleto.==. Database.Esqueleto.nothing, rhs: Database.Esqueleto.isNothing v, name: Use Esqueleto's isNothing}
- error: {lhs: v Database.Esqueleto.==. Database.Esqueleto.val Nothing, rhs: Database.Esqueleto.isNothing v, name: Use Esqueleto's isNothing}
- error: {lhs: v Database.Esqueleto.!=. Database.Esqueleto.nothing, rhs: not_ (Database.Esqueleto.isNothing v), name: Use Esqueleto's not isNothing}
- error: {lhs: v Database.Esqueleto.!=. Database.Esqueleto.val Nothing, rhs: not_ (Database.Esqueleto.isNothing v), name: Use Esqueleto's not isNothing}

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

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

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

Project a field of an entity that may be null.

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

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

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

Project a field of an entity.

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

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: esqueleto-3.2.0

subSelectForeign #

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: esqueleto-3.2.0

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

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: esqueleto-3.2.0

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

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: esqueleto-3.2.0

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

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: esqueleto-3.2.0

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

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: esqueleto-3.2.0

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

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.

locking :: LockingKind -> SqlQuery () #

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: esqueleto-2.2.7

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

HAVING.

Since: esqueleto-1.2.2

rand :: SqlExpr OrderBy #

ORDER BY random() clause.

Since: esqueleto-1.3.10

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

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: esqueleto-2.2.4

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

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

Since: esqueleto-2.2.4

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

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: esqueleto-2.2.4

distinct :: SqlQuery a -> SqlQuery a #

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: esqueleto-2.2.4

offset :: Int64 -> SqlQuery () #

OFFSET. Usually used with limit.

limit :: Int64 -> SqlQuery () #

LIMIT. Limit the number of returned rows.

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

Descending order of this field or SqlExpression.

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

Ascending order of this field or SqlExpression.

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

ORDER BY clause. See also asc and desc.

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

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

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)

Need more columns?

The ToSomeValues class is defined for SqlExpr and tuples of SqlExprs. We only have definitions for up to 8 elements in a tuple right now, so it's possible that you may need to have more than 8 elements.

For example, consider a query with a groupBy call like this:

groupBy (e0, e1, e2, e3, e4, e5, e6, e7)

This is the biggest you can get with a single tuple. However, you can easily nest the tuples to add more:

groupBy ((e0, e1, e2, e3, e4, e5, e6, e7), e8, e9)

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

WHERE clause: restrict the query's result.

newtype Value a #

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

Constructors

Value 

Fields

Instances

Instances details
Applicative Value 
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 #

Functor Value

Since: esqueleto-1.4.4

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Monad Value 
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 #

(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Entity rec)) (SqlExpr (Value typ))

This instance allows you to use record.field notation with GHC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
BlogPost
    authorId     PersonId
    title        Text

-- query:
select $ do
    bp <- from $ table @BlogPost
    pure $ bp.title

This is exactly equivalent to the following:

blogPost :: SqlExpr (Entity BlogPost)

blogPost ^. BlogPostTitle
blogPost ^. #title
blogPost.title

There's another instance defined on SqlExpr (Entity (Maybe rec)), which allows you to project from a LEFT JOINed entity.

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Entity rec) -> SqlExpr (Value typ) #

(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Maybe (Entity rec))) (SqlExpr (Value (Maybe typ)))

This instance allows you to use record.field notation with GC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
Person
    name         Text

BlogPost
    title        Text
    authorId     PersonId

-- query:

select $ do
    (p :& bp) <- from $
        table Person
        leftJoin table BlogPost
        on do
            \(p :& bp) ->
                just p.id ==. bp.authorId
    pure (p.name, bp.title)

The following forms are all equivalent:

blogPost :: SqlExpr (Maybe (Entity BlogPost))

blogPost ?. BlogPostTitle
blogPost ?. #title
blogPost.title

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Maybe (Entity rec)) -> SqlExpr (Value (Maybe typ)) #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b, d ~ (a' :& b)) => DoInnerJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doInnerJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d #

(ToFrom a a', ToMaybe b, d ~ (a' :& ToMaybeT b), SqlSelect b r, ToAlias b, ToAliasReference b) => DoLeftJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doLeftJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d #

Show a => Show (Value a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

show :: Value a -> String #

showList :: [Value a] -> ShowS #

ToAlias (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a)) #

ToAliasReference (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToMaybe (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Value a)) #

Methods

toMaybe :: SqlExpr (Value a) -> ToMaybeT (SqlExpr (Value a)) #

ToSomeValues (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toSomeValues :: SqlExpr (Value a) -> [SomeValue] #

Eq a => Eq (Value a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Ord a => Ord (Value a) 
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 #

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

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

Instance details

Defined in Database.Esqueleto.Internal.Internal

type ToMaybeT (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

newtype ValueList a #

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

Instances details
Show a => Show (ValueList a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Eq a => Eq (ValueList a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Ord a => Ord (ValueList a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

data InnerJoin a b infixl 2 #

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

Constructors

a `InnerJoin` b infixl 2 

Instances

Instances details
IsJoinKind InnerJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

smartJoin :: a -> b -> InnerJoin a b #

reifyJoinKind :: InnerJoin a b -> JoinKind #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (InnerJoin a b) #

data CrossJoin a b infixl 2 #

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

Constructors

a `CrossJoin` b infixl 2 

Instances

Instances details
IsJoinKind CrossJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

smartJoin :: a -> b -> CrossJoin a b #

reifyJoinKind :: CrossJoin a b -> JoinKind #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (CrossJoin a b) #

data LeftOuterJoin a b infixl 2 #

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 

Instances

Instances details
IsJoinKind LeftOuterJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

smartJoin :: a -> b -> LeftOuterJoin a b #

reifyJoinKind :: LeftOuterJoin a b -> JoinKind #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (LeftOuterJoin a b) #

data RightOuterJoin a b infixl 2 #

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

Constructors

a `RightOuterJoin` b infixl 2 

Instances

Instances details
IsJoinKind RightOuterJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (RightOuterJoin a b) #

data FullOuterJoin a b infixl 2 #

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

Constructors

a `FullOuterJoin` b infixl 2 

Instances

Instances details
IsJoinKind FullOuterJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

smartJoin :: a -> b -> FullOuterJoin a b #

reifyJoinKind :: FullOuterJoin a b -> JoinKind #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (FullOuterJoin a b) #

data JoinKind #

(Internal) A kind of JOIN.

Constructors

InnerJoinKind
INNER JOIN
CrossJoinKind
CROSS JOIN
LeftOuterJoinKind
LEFT OUTER JOIN
RightOuterJoinKind
RIGHT OUTER JOIN
FullOuterJoinKind
FULL OUTER JOIN

Instances

Instances details
Show JoinKind 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Eq JoinKind 
Instance details

Defined in Database.Esqueleto.Internal.Internal

data OnClauseWithoutMatchingJoinException #

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

Instances

Instances details
Exception OnClauseWithoutMatchingJoinException 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Show OnClauseWithoutMatchingJoinException 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Eq OnClauseWithoutMatchingJoinException 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Ord OnClauseWithoutMatchingJoinException 
Instance details

Defined in Database.Esqueleto.Internal.Internal

data OrderBy #

Phantom type used by orderBy, asc and desc.

data DistinctOn #

Phantom type used by distinctOn and don.

data LockingKind #

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: esqueleto-2.2.7

Constructors

ForUpdate

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

Since: esqueleto-2.2.7

ForUpdateSkipLocked

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

Since: esqueleto-2.2.7

ForShare

FOR SHARE syntax. Supported by PostgreSQL.

Since: esqueleto-2.2.7

LockInShareMode

LOCK IN SHARE MODE syntax. Supported by MySQL.

Since: esqueleto-2.2.7

class PersistField a => SqlString a #

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: esqueleto-2.4.0

Instances

Instances details
SqlString Html

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString ByteString

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString Text

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString Text

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString a => SqlString (Maybe a)

Since: esqueleto-2.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

a ~ Char => SqlString [a]

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

type family BaseEnt ent #

e.g. type BaseEnt MyBase = MyChild

class ToBaseId ent where #

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 #

e.g. type BaseEnt MyBase = MyChild

Methods

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

Convert from the key of the BaseEnt(ity) to the key of the child entity. This function is not actually called, but that it typechecks proves this operation is safe.

data SqlQuery a #

SQL backend for esqueleto using SqlPersistT.

Instances

Instances details
Applicative SqlQuery 
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 #

Functor SqlQuery 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Monad SqlQuery 
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 #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b, d ~ (a' :& b)) => DoInnerJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doInnerJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d #

(ToFrom a a', ToMaybe b, d ~ (a' :& ToMaybeT b), SqlSelect b r, ToAlias b, ToAliasReference b) => DoLeftJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doLeftJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b) => DoCrossJoin Lateral a (a' -> SqlQuery b) (a' :& b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doCrossJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b) -> From (a' :& b) #

(SqlSelect a r, ToAlias a, ToAliasReference a) => ToFrom (SubQuery (SqlQuery a)) a 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: SubQuery (SqlQuery a) -> From a #

(SqlSelect a r, ToAlias a, ToAliasReference a) => ToFrom (SqlQuery a) a 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: SqlQuery a -> From a #

(SqlSelect a r, ToAlias a, ToAliasReference a) => ToSqlSetOperation (SqlQuery a) a 
Instance details

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

ValidOnClause (a -> SqlQuery b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

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

Constraint synonym for persistent entities whose backend is SqlBackend.

data SqlExpr a #

An expression on the SQL backend.

Raw expression: Contains a SqlExprMeta and a function for building the expr. It recieves a parameter telling it whether it is in a parenthesized context, and takes information about the SQL connection (mainly for escaping names) and returns both an string (Builder) and a list of values to be interpolated by the SQL backend.

Instances

Instances details
(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Entity rec)) (SqlExpr (Value typ))

This instance allows you to use record.field notation with GHC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
BlogPost
    authorId     PersonId
    title        Text

-- query:
select $ do
    bp <- from $ table @BlogPost
    pure $ bp.title

This is exactly equivalent to the following:

blogPost :: SqlExpr (Entity BlogPost)

blogPost ^. BlogPostTitle
blogPost ^. #title
blogPost.title

There's another instance defined on SqlExpr (Entity (Maybe rec)), which allows you to project from a LEFT JOINed entity.

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Entity rec) -> SqlExpr (Value typ) #

(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Maybe (Entity rec))) (SqlExpr (Value (Maybe typ)))

This instance allows you to use record.field notation with GC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
Person
    name         Text

BlogPost
    title        Text
    authorId     PersonId

-- query:

select $ do
    (p :& bp) <- from $
        table Person
        leftJoin table BlogPost
        on do
            \(p :& bp) ->
                just p.id ==. bp.authorId
    pure (p.name, bp.title)

The following forms are all equivalent:

blogPost :: SqlExpr (Maybe (Entity BlogPost))

blogPost ?. BlogPostTitle
blogPost ?. #title
blogPost.title

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Maybe (Entity rec)) -> SqlExpr (Value (Maybe typ)) #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b, d ~ (a' :& b)) => DoInnerJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doInnerJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d #

(ToFrom a a', ToMaybe b, d ~ (a' :& ToMaybeT b), SqlSelect b r, ToAlias b, ToAliasReference b) => DoLeftJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doLeftJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d #

ToAlias (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a)) #

ToAlias (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a)) #

ToAlias (SqlExpr (Maybe (Entity a))) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Maybe (Entity a)) -> SqlQuery (SqlExpr (Maybe (Entity a))) #

ToAliasReference (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToAliasReference (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToAliasReference (SqlExpr (Maybe (Entity a))) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToMaybe (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Value a)) #

Methods

toMaybe :: SqlExpr (Value a) -> ToMaybeT (SqlExpr (Value a)) #

ToMaybe (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Entity a)) #

Methods

toMaybe :: SqlExpr (Entity a) -> ToMaybeT (SqlExpr (Entity a)) #

ToMaybe (SqlExpr (Maybe a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Maybe a)) #

Methods

toMaybe :: SqlExpr (Maybe a) -> ToMaybeT (SqlExpr (Maybe a)) #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

ToSomeValues (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toSomeValues :: SqlExpr (Value a) -> [SomeValue] #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

PersistEntity ent => ToFrom (Table ent) (SqlExpr (Entity ent)) 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: Table ent -> From (SqlExpr (Entity ent)) #

PersistEntity e => SqlSelect (SqlExpr (Insertion e)) (Insertion e)

INSERT INTO hack.

Instance details

Defined in Database.Esqueleto.Internal.Internal

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

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

Instance details

Defined in Database.Esqueleto.Internal.Internal

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

You may return an Entity from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

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

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

Instance details

Defined in Database.Esqueleto.Internal.Internal

type ToMaybeT (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (SqlExpr (Maybe a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

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 #

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

Instances details
(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) #

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 PersistConfigBackend c :: (Type -> Type) -> Type -> Type #

Instances

Instances details
type PersistConfigBackend (Either c1 c2) 
Instance details

Defined in Database.Persist.Class.PersistConfig

type family PersistConfigPool c #

Instances

Instances details
type PersistConfigPool (Either c1 c2) 
Instance details

Defined in Database.Persist.Class.PersistConfig

newtype ConstraintNameHS #

An ConstraintNameHS represents the Haskell-side name that persistent will use for a constraint.

Since: persistent-2.12.0.0

Constructors

ConstraintNameHS 

newtype ConstraintNameDB #

A ConstraintNameDB represents the datastore-side name that persistent will use for a constraint.

Since: persistent-2.12.0.0

Constructors

ConstraintNameDB 

Instances

Instances details
Read ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

Show ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

Eq ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

Ord ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

DatabaseName ConstraintNameDB

Since: persistent-2.12.0.0

Instance details

Defined in Database.Persist.Names

Methods

escapeWith :: (Text -> str) -> ConstraintNameDB -> str #

Lift ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

Methods

lift :: Quote m => ConstraintNameDB -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ConstraintNameDB -> Code m ConstraintNameDB #

newtype EntityNameDB #

An EntityNameDB represents the datastore-side name that persistent will use for an entity.

Since: persistent-2.12.0.0

Constructors

EntityNameDB 

Fields

newtype EntityNameHS #

An EntityNameHS represents the Haskell-side name that persistent will use for an entity.

Since: persistent-2.12.0.0

Constructors

EntityNameHS 

Fields

newtype FieldNameHS #

A FieldNameHS represents the Haskell-side name that persistent will use for a field.

Since: persistent-2.12.0.0

Constructors

FieldNameHS 

Fields

newtype FieldNameDB #

An EntityNameDB represents the datastore-side name that persistent will use for an entity.

Since: persistent-2.12.0.0

Constructors

FieldNameDB 

Fields

Instances

Instances details
Read FieldNameDB 
Instance details

Defined in Database.Persist.Names

Show FieldNameDB 
Instance details

Defined in Database.Persist.Names

Eq FieldNameDB 
Instance details

Defined in Database.Persist.Names

Ord FieldNameDB 
Instance details

Defined in Database.Persist.Names

DatabaseName FieldNameDB

Since: persistent-2.12.0.0

Instance details

Defined in Database.Persist.Names

Methods

escapeWith :: (Text -> str) -> FieldNameDB -> str #

Lift FieldNameDB 
Instance details

Defined in Database.Persist.Names

Methods

lift :: Quote m => FieldNameDB -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FieldNameDB -> Code m FieldNameDB #

class DatabaseName a where #

Convenience operations for working with '-NameDB' types.

Since: persistent-2.12.0.0

Methods

escapeWith :: (Text -> str) -> a -> str #

Instances

Instances details
DatabaseName ConstraintNameDB

Since: persistent-2.12.0.0

Instance details

Defined in Database.Persist.Names

Methods

escapeWith :: (Text -> str) -> ConstraintNameDB -> str #

DatabaseName EntityNameDB 
Instance details

Defined in Database.Persist.Names

Methods

escapeWith :: (Text -> str) -> EntityNameDB -> str #

DatabaseName FieldNameDB

Since: persistent-2.12.0.0

Instance details

Defined in Database.Persist.Names

Methods

escapeWith :: (Text -> str) -> FieldNameDB -> str #

data LiteralType #

A type that determines how a backend should handle the literal.

Since: persistent-2.12.0.0

Constructors

Escaped

The accompanying value will be escaped before inserting into the database. This is the correct default choice to use.

Since: persistent-2.12.0.0

Unescaped

The accompanying value will not be escaped when inserting into the database. This is potentially dangerous - use this with care.

Since: persistent-2.12.0.0

DbSpecific

The DbSpecific constructor corresponds to the legacy PersistDbSpecific constructor. We need to keep this around because old databases may have serialized JSON representations that reference this. We don't want to break the ability of a database to load rows.

Since: persistent-2.12.0.0

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

PersistLiteral_ LiteralType ByteString

This constructor is used to specify some raw literal value for the backend. The LiteralType value specifies how the value should be escaped. This can be used to make special, custom types avaialable in the back end.

Since: persistent-2.12.0.0

Bundled Patterns

pattern PersistLiteral :: ByteString -> PersistValue

This pattern synonym used to be a data constructor on PersistValue, but was changed into a catch-all pattern synonym to allow backwards compatiblity with database types. See the documentation on PersistDbSpecific for more details.

Since: persistent-2.12.0.0

pattern PersistDbSpecific :: ByteString -> PersistValue

This pattern synonym used to be a data constructor for the PersistValue type. It was changed to be a pattern so that JSON-encoded database values could be parsed into their corresponding values. You should not use this, and instead prefer to pattern match on PersistLiteral_ directly.

If you use this, it will overlap a patern match on the 'PersistLiteral_, PersistLiteral, and PersistLiteralEscaped patterns. If you need to disambiguate between these constructors, pattern match on PersistLiteral_ directly.

Since: persistent-2.12.0.0

pattern PersistLiteralEscaped :: ByteString -> PersistValue

This pattern synonym used to be a data constructor on PersistValue, but was changed into a catch-all pattern synonym to allow backwards compatiblity with database types. See the documentation on PersistDbSpecific for more details.

Since: persistent-2.12.0.0

Instances

Instances details
FromJSON PersistValue 
Instance details

Defined in Database.Persist.PersistValue

ToJSON PersistValue 
Instance details

Defined in Database.Persist.PersistValue

Read PersistValue 
Instance details

Defined in Database.Persist.PersistValue

Show PersistValue 
Instance details

Defined in Database.Persist.PersistValue

Eq PersistValue 
Instance details

Defined in Database.Persist.PersistValue

Ord PersistValue 
Instance details

Defined in Database.Persist.PersistValue

FromHttpApiData PersistValue 
Instance details

Defined in Database.Persist.PersistValue

ToHttpApiData PersistValue 
Instance details

Defined in Database.Persist.PersistValue

PathPiece PersistValue 
Instance details

Defined in Database.Persist.PersistValue

PersistField PersistValue 
Instance details

Defined in Database.Persist.Class.PersistField

PersistFieldSql PersistValue 
Instance details

Defined in Database.Persist.Sql.Class

data IsolationLevel #

Please refer to the documentation for the database in question for a full overview of the semantics of the varying isloation levels

Instances

Instances details
Bounded IsolationLevel 
Instance details

Defined in Database.Persist.SqlBackend.Internal.IsolationLevel

Enum IsolationLevel 
Instance details

Defined in Database.Persist.SqlBackend.Internal.IsolationLevel

Show IsolationLevel 
Instance details

Defined in Database.Persist.SqlBackend.Internal.IsolationLevel

Eq IsolationLevel 
Instance details

Defined in Database.Persist.SqlBackend.Internal.IsolationLevel

Ord IsolationLevel 
Instance details

Defined in Database.Persist.SqlBackend.Internal.IsolationLevel

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

Instances

Instances details
Read FieldDef 
Instance details

Defined in Database.Persist.Types.Base

Show FieldDef 
Instance details

Defined in Database.Persist.Types.Base

Eq FieldDef 
Instance details

Defined in Database.Persist.Types.Base

Ord FieldDef 
Instance details

Defined in Database.Persist.Types.Base

Lift FieldDef 
Instance details

Defined in Database.Persist.Types.Base

Methods

lift :: Quote m => FieldDef -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FieldDef -> Code m FieldDef #

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

Instances

Instances details
Read SqlType 
Instance details

Defined in Database.Persist.Types.Base

Show SqlType 
Instance details

Defined in Database.Persist.Types.Base

Eq SqlType 
Instance details

Defined in Database.Persist.Types.Base

Methods

(==) :: SqlType -> SqlType -> Bool #

(/=) :: SqlType -> SqlType -> Bool #

Ord SqlType 
Instance details

Defined in Database.Persist.Types.Base

Lift SqlType 
Instance details

Defined in Database.Persist.Types.Base

Methods

lift :: Quote m => SqlType -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => SqlType -> Code m SqlType #

data FieldCascade #

This datatype describes how a foreign reference field cascades deletes or updates.

This type is used in both parsing the model definitions and performing migrations. A Nothing in either of the field values means that the user has not specified a CascadeAction. An unspecified CascadeAction is defaulted to Restrict when doing migrations.

Since: persistent-2.11.0

data ForeignDef #

Constructors

ForeignDef 

Fields

type ForeignFieldDef = (FieldNameHS, FieldNameDB) #

Used instead of FieldDef to generate a smaller amount of code

data UniqueDef #

Type for storing the Uniqueness constraint in the Schema. Assume you have the following schema with a uniqueness constraint:

Person
  name String
  age Int
  UniqueAge age

This will be represented as:

UniqueDef
    { uniqueHaskell = ConstraintNameHS (packPTH UniqueAge)
    , uniqueDBName = ConstraintNameDB (packPTH "unique_age")
    , uniqueFields = [(FieldNameHS (packPTH "age"), FieldNameDB (packPTH "age"))]
    , uniqueAttrs = []
    }

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 

data EmbedEntityDef #

An EmbedEntityDef is the same as an EntityDef But it is only used for fieldReference so it only has data needed for embedding

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 !EntityNameHS

A ForeignRef has a late binding to the EntityDef it references via name and has the Haskell type of the foreign key in the form of FieldType

EmbedRef EntityNameHS 
CompositeRef CompositeDef 
SelfReference

A SelfReference stops an immediate cycle which causes non-termination at compile-time (issue #311).

data FieldType #

A FieldType describes a field parsed from the QuasiQuoter and is used to determine the Haskell type in the generated code.

name Text parses into FTTypeCon Nothing Text

name T.Text parses into FTTypeCon (Just T Text)

name (Jsonb User) parses into:

FTApp (FTTypeCon Nothing Jsonb) (FTTypeCon Nothing User)

Constructors

FTTypeCon (Maybe Text) Text

Optional module and name.

FTTypePromoted Text 
FTApp FieldType FieldType 
FTList FieldType 

data FieldAttr #

Attributes that may be attached to fields that can affect migrations and serialization in backend-specific ways.

While we endeavor to, we can't forsee all use cases for all backends, and so FieldAttr is extensible through its constructor FieldAttrOther.

Since: persistent-2.11.0.0

Constructors

FieldAttrMaybe

The Maybe keyword goes after the type. This indicates that the column is nullable, and the generated Haskell code will have a Maybe type for it.

Example:

User
    name Text Maybe
FieldAttrNullable

This indicates that the column is nullable, but should not have a Maybe type. For this to work out, you need to ensure that the PersistField instance for the type in question can support a PersistNull value.

data What = NoWhat | Hello Text

instance PersistField What where
    fromPersistValue PersistNull =
        pure NoWhat
    fromPersistValue pv =
        Hello $ fromPersistValue pv

instance PersistFieldSql What where
    sqlType _ = SqlString

User
    what What nullable
FieldAttrMigrationOnly

This tag means that the column will not be present on the Haskell code, but will not be removed from the database. Useful to deprecate fields in phases.

You should set the column to be nullable in the database. Otherwise, inserts won't have values.

User
    oldName Text MigrationOnly
    newName Text
FieldAttrSafeToRemove

A SafeToRemove attribute is not present on the Haskell datatype, and the backend migrations should attempt to drop the column without triggering any unsafe migration warnings.

Useful after you've used MigrationOnly to remove a column from the database in phases.

User
    oldName Text SafeToRemove
    newName Text
FieldAttrNoreference

This attribute indicates that we should create a foreign key reference from a column. By default, persistent will try and create a foreign key reference for a column if it can determine that the type of the column is a Key entity or an EntityId and the Entity's name was present in mkPersist.

This is useful if you want to use the explicit foreign key syntax.

Post
    title    Text

Comment
    postId   PostId      noreference
    Foreign Post fk_comment_post postId
FieldAttrReference Text

This is set to specify precisely the database table the column refers to.

Post
    title    Text

Comment
    postId   PostId references="post"

You should not need this - persistent should be capable of correctly determining the target table's name. If you do need this, please file an issue describing why.

FieldAttrConstraint Text

Specify a name for the constraint on the foreign key reference for this table.

Post
    title    Text

Comment
    postId   PostId constraint="my_cool_constraint_name"
FieldAttrDefault Text

Specify the default value for a column.

User
    createdAt    UTCTime     default="NOW()"

Note that a default= attribute does not mean you can omit the value while inserting.

FieldAttrSqltype Text

Specify a custom SQL type for the column. Generally, you should define a custom datatype with a custom PersistFieldSql instance instead of using this.

User
    uuid     Text    sqltype=UUID
FieldAttrMaxlen Integer

Set a maximum length for a column. Useful for VARCHAR and indexes.

User
    name     Text    maxlen=200

    UniqueName name
FieldAttrSql Text

Specify the database name of the column.

User
    blarghle     Int     sql="b_l_a_r_g_h_l_e"

Useful for performing phased migrations, where one column is renamed to another column over time.

FieldAttrOther Text

A grab bag of random attributes that were unrecognized by the parser.

type Attr = Text #

type ExtraLine = [Text] #

data EntityIdDef #

The definition for the entity's primary key ID.

Since: persistent-2.13.0.0

Constructors

EntityIdField !FieldDef

The entity has a single key column, and it is a surrogate key - that is, you can't go from rec -> Key rec.

Since: persistent-2.13.0.0

EntityIdNaturalKey !CompositeDef

The entity has a natural key. This means you can write rec -> Key rec because all the key fields are present on the datatype.

A natural key can have one or more columns.

Since: persistent-2.13.0.0

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.

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.

Instances

Instances details
Show WhyNullable 
Instance details

Defined in Database.Persist.Types.Base

Eq WhyNullable 
Instance details

Defined in Database.Persist.Types.Base

data IsNullable #

Instances

Instances details
Show IsNullable 
Instance details

Defined in Database.Persist.Types.Base

Eq IsNullable 
Instance details

Defined in Database.Persist.Types.Base

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

Instances details
Bounded Checkmark 
Instance details

Defined in Database.Persist.Types.Base

Enum 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

Eq Checkmark 
Instance details

Defined in Database.Persist.Types.Base

Ord Checkmark 
Instance details

Defined in Database.Persist.Types.Base

FromHttpApiData Checkmark 
Instance details

Defined in Database.Persist.Types.Base

ToHttpApiData Checkmark 
Instance details

Defined in Database.Persist.Types.Base

PathPiece Checkmark 
Instance details

Defined in Database.Persist.Types.Base

PersistField Checkmark 
Instance details

Defined in Database.Persist.Class.PersistField

PersistFieldSql Checkmark 
Instance details

Defined in Database.Persist.Sql.Class

entitiesPrimary :: EntityDef -> NonEmpty FieldDef #

Return the [FieldDef] for the entity keys.

keyAndEntityFields :: EntityDef -> NonEmpty FieldDef #

Returns a NonEmpty list of FieldDef that correspond with the key columns for an EntityDef.

parseFieldAttrs :: [Text] -> [FieldAttr] #

Parse raw field attributes into structured form. Any unrecognized attributes will be preserved, identically as they are encountered, as FieldAttrOther values.

Since: persistent-2.11.0.0

isHaskellField :: FieldDef -> Bool #

Returns True if the FieldDef does not have a MigrationOnly or SafeToRemove flag from the QuasiQuoter.

Since: persistent-2.13.0.0

noCascade :: FieldCascade #

A FieldCascade that does nothing.

Since: persistent-2.11.0

renderFieldCascade :: FieldCascade -> Text #

Renders a FieldCascade value such that it can be used in SQL migrations.

Since: persistent-2.11.0

renderCascadeAction :: CascadeAction -> Text #

Render a CascadeAction to Text such that it can be used in a SQL command.

Since: persistent-2.11.0

data Statement #

A Statement is a representation of a database query that has been prepared and stored on the server side.

Constructors

Statement 

Fields

type LogFunc = Loc -> LogSource -> LogLevel -> LogStr -> IO () #

setFieldAttrs :: [FieldAttr] -> FieldDef -> FieldDef #

Replace the FieldDef FieldAttr with the new list.

Since: persistent-2.13.0.0

overFieldAttrs :: ([FieldAttr] -> [FieldAttr]) -> FieldDef -> FieldDef #

Modify the list of field attributes.

Since: persistent-2.13.0.0

addFieldAttr :: FieldAttr -> FieldDef -> FieldDef #

Add an attribute to the list of field attributes.

Since: persistent-2.13.0.0

isFieldNullable :: FieldDef -> IsNullable #

Check if the field definition is nullable

Since: persistent-2.13.0.0

isFieldMaybe :: FieldDef -> Bool #

Check if the field is `Maybe a`

Since: persistent-2.13.0.0

getEntityUniques :: EntityDef -> [UniqueDef] #

Retrieve the list of UniqueDef from an EntityDef. This currently does not include a Primary key, if one is defined. A future version of persistent will include a Primary key among the Unique constructors for the Entity.

Since: persistent-2.13.0.0

getEntityHaskellName :: EntityDef -> EntityNameHS #

Retrieve the Haskell name of the given entity.

Since: persistent-2.13.0.0

getEntityDBName :: EntityDef -> EntityNameDB #

Return the database name for the given entity.

Since: persistent-2.13.0.0

setEntityDBName :: EntityNameDB -> EntityDef -> EntityDef #

Since: persistent-2.13.0.0

getEntityForeignDefs :: EntityDef -> [ForeignDef] #

Since: persistent-2.13.0.0

getEntityFields :: EntityDef -> [FieldDef] #

Retrieve the list of FieldDef that makes up the fields of the entity.

This does not return the fields for an Id column or an implicit id. It will return the key columns if you used the Primary syntax for defining the primary key.

This does not return fields that are marked SafeToRemove or MigrationOnly - so it only returns fields that are represented in the Haskell type. If you need those fields, use getEntityFieldsDatabase.

Since: persistent-2.13.0.0

getEntityFieldsDatabase :: EntityDef -> [FieldDef] #

This returns all of the FieldDef defined for the EntityDef, including those fields that are marked as MigrationOnly (and therefore only present in the database) or SafeToRemove (and a migration will drop the column if it exists in the database).

For all the fields that are present on the Haskell-type, see getEntityFields.

Since: persistent-2.13.0.0

isEntitySum :: EntityDef -> Bool #

Since: persistent-2.13.0.0

getEntityId :: EntityDef -> EntityIdDef #

Since: persistent-2.13.0.0

getEntityIdField :: EntityDef -> Maybe FieldDef #

Since: persistent-2.13.0.0

setEntityId :: FieldDef -> EntityDef -> EntityDef #

Set an entityId to be the given FieldDef.

Since: persistent-2.13.0.0

setEntityIdDef :: EntityIdDef -> EntityDef -> EntityDef #

Since: persistent-2.13.0.0

getEntityKeyFields :: EntityDef -> NonEmpty FieldDef #

Since: persistent-2.13.0.0

overEntityFields :: ([FieldDef] -> [FieldDef]) -> EntityDef -> EntityDef #

Perform a mapping function over all of the entity fields, as determined by getEntityFieldsDatabase.

Since: persistent-2.13.0.0

newtype OverflowNatural #

Prior to persistent-2.11.0, we provided an instance of PersistField for the Natural type. This was in error, because Natural represents an infinite value, and databases don't have reasonable types for this.

The instance for Natural used the Int64 underlying type, which will cause underflow and overflow errors. This type has the exact same code in the instances, and will work seamlessly.

A more appropriate type for this is the Word series of types from Data.Word. These have a bounded size, are guaranteed to be non-negative, and are quite efficient for the database to store.

Since: persistent-2.11.0

Constructors

OverflowNatural 

Instances

Instances details
Num OverflowNatural 
Instance details

Defined in Database.Persist.Class.PersistField

Show OverflowNatural 
Instance details

Defined in Database.Persist.Class.PersistField

Eq OverflowNatural 
Instance details

Defined in Database.Persist.Class.PersistField

Ord OverflowNatural 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField OverflowNatural 
Instance details

Defined in Database.Persist.Class.PersistField

PersistFieldSql OverflowNatural

This type uses the SqlInt64 version, which will exhibit overflow and underflow behavior. Additionally, it permits negative values in the database, which isn't ideal.

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

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

Instances details
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 Int8 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Rational 
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 Html 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField ByteString 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField OverflowNatural 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField SomePersistField 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField PersistValue 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Checkmark 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Text 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Text 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Day 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField UTCTime 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField TimeOfDay 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Word8 
Instance details

Defined in Database.Persist.Class.PersistField

(TypeError ((((('Text "The instance of PersistField for the Natural type was removed." :$$: 'Text "Please see the documentation for OverflowNatural if you want to ") :$$: 'Text "continue using the old behavior or want to see documentation on ") :$$: 'Text "why the instance was removed.") :$$: 'Text "") :$$: 'Text "This error instance will be removed in a future release.") :: Constraint) => PersistField Natural 
Instance details

Defined in Database.Persist.Class.PersistField

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

PersistField a => PersistField (Maybe a) 
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

HasResolution a => PersistField (Fixed a) 
Instance details

Defined in Database.Persist.Class.PersistField

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

Defined in Database.Persist.Class.PersistField

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

Defined in Database.Persist.Class.PersistField

class SymbolToField (sym :: Symbol) rec typ | sym rec -> typ where #

This type class is used with the OverloadedLabels extension to provide a more convenient means of using the EntityField type. EntityField definitions are prefixed with the type name to avoid ambiguity, but this ambiguity can result in verbose code.

If you have a table User with a name Text field, then the corresponding EntityField is UserName. With this, we can write #name :: EntityField User Text.

What's more fun is that the type is more general: it's actually #name :: (SymbolToField "name" rec typ) => EntityField rec typ

Which means it is *polymorphic* over the actual record. This allows you to write code that can be generic over the tables, provided they have the right fields.

Since: persistent-2.11.0.0

Methods

symbolToField :: EntityField rec typ #

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

Instances details
(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Entity rec)) (SqlExpr (Value typ))

This instance allows you to use record.field notation with GHC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
BlogPost
    authorId     PersonId
    title        Text

-- query:
select $ do
    bp <- from $ table @BlogPost
    pure $ bp.title

This is exactly equivalent to the following:

blogPost :: SqlExpr (Entity BlogPost)

blogPost ^. BlogPostTitle
blogPost ^. #title
blogPost.title

There's another instance defined on SqlExpr (Entity (Maybe rec)), which allows you to project from a LEFT JOINed entity.

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Entity rec) -> SqlExpr (Value typ) #

(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Maybe (Entity rec))) (SqlExpr (Value (Maybe typ)))

This instance allows you to use record.field notation with GC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
Person
    name         Text

BlogPost
    title        Text
    authorId     PersonId

-- query:

select $ do
    (p :& bp) <- from $
        table Person
        leftJoin table BlogPost
        on do
            \(p :& bp) ->
                just p.id ==. bp.authorId
    pure (p.name, bp.title)

The following forms are all equivalent:

blogPost :: SqlExpr (Maybe (Entity BlogPost))

blogPost ?. BlogPostTitle
blogPost ?. #title
blogPost.title

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Maybe (Entity rec)) -> SqlExpr (Value (Maybe typ)) #

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

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

ToAlias (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a)) #

ToAlias (SqlExpr (Maybe (Entity a))) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Maybe (Entity a)) -> SqlQuery (SqlExpr (Maybe (Entity a))) #

ToAliasReference (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToAliasReference (SqlExpr (Maybe (Entity a))) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToMaybe (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Entity a)) #

Methods

toMaybe :: SqlExpr (Entity a) -> ToMaybeT (SqlExpr (Entity a)) #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

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

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

Defined in Database.Persist.Class.PersistEntity

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

Defined in Database.Persist.Sql.Class

Methods

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

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

Defined in Database.Persist.Sql.Class

Methods

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

rawSqlColCountReason :: Entity record -> String #

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

PersistEntity ent => ToFrom (Table ent) (SqlExpr (Entity ent)) 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: Table ent -> From (SqlExpr (Entity ent)) #

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

You may return an Entity from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

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

You may return a possibly-NULL 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.13.3.5-JQO0xSplhu4Dob8Xs9toj2" '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)))
type ToMaybeT (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

data FilterValue typ where #

Value to filter with. Highly dependant on the type of filter used.

Since: persistent-2.10.0

Constructors

FilterValue :: forall typ. typ -> FilterValue typ 
FilterValues :: forall typ. [typ] -> FilterValue typ 
UnsafeValue :: forall a typ. PersistField a => a -> FilterValue typ 

type family BackendSpecificUpdate backend 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 #

Persistent allows multiple different backends (databases).

data Key record #

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

data EntityField record :: Type -> Type #

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

As of persistent-2.11.0.0, it's possible to use the OverloadedLabels language extension to refer to EntityField values polymorphically. See the documentation on SymbolToField for more information.

data Unique record #

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 :: proxy 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 -> NonEmpty (FieldNameHS, FieldNameDB) #

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.

keyFromRecordM :: Maybe (record -> Key record) #

Extract a Key record from a record value. Currently, this is only defined for entities using the Primary syntax for natural/composite keys. In a future version of persistent which incorporates the ID directly into the entity, this will always be Just.

Since: persistent-2.11.0.0

type family PersistEntityBackend record #

Persistent allows multiple different backends (databases).

data family Key record #

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

Instances

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

Defined in Database.Persist.Sql.Class

data family EntityField record :: Type -> Type #

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

As of persistent-2.11.0.0, it's possible to use the OverloadedLabels language extension to refer to EntityField values polymorphically. See the documentation on SymbolToField for more information.

Instances

Instances details
SymbolToField sym rec typ => IsLabel sym (EntityField rec typ)

This instance delegates to SymbolToField to provide OverloadedLabels support to the EntityField type.

Since: persistent-2.11.0.0

Instance details

Defined in Database.Persist.Class.PersistEntity

Methods

fromLabel :: EntityField rec typ #

data family Unique record #

Unique keys besides the Key.

Instances

Instances details
FinalResult (Unique val) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

finalR :: Unique val -> KnowResult (Unique val) #

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

Get list of values corresponding to given entity.

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

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

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

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

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

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

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

insertMany :: forall record (m :: Type -> Type). (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   |
+-----+------+-----+

repsert :: forall record (m :: Type -> Type). (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 :: forall record (m :: Type -> Type). (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 :: forall record (m :: Type -> Type). (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 :: forall record (m :: Type -> Type). (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 (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 #

Minimal complete definition

get

class PersistCore backend #

Associated Types

data BackendKey backend #

data family BackendKey backend #

Instances

Instances details
newtype BackendKey SqlReadBackend 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

newtype BackendKey SqlWriteBackend 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

newtype BackendKey SqlBackend 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlReadBackend) 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlReadBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.13.3.5-JQO0xSplhu4Dob8Xs9toj2" 'True) (C1 ('MetaCons "SqlReadBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlReadBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))
type Rep (BackendKey SqlWriteBackend) 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlWriteBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.13.3.5-JQO0xSplhu4Dob8Xs9toj2" 'True) (C1 ('MetaCons "SqlWriteBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlWriteBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))
type Rep (BackendKey SqlBackend) 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.13.3.5-JQO0xSplhu4Dob8Xs9toj2" 'True) (C1 ('MetaCons "SqlBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))

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 #

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

A convenient alias for common type signatures

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' = withCompatibleBackend asdf

Since: persistent-2.7.1

Methods

projectBackend :: sub -> sup #

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

Methods

persistBackend :: backend -> BaseBackend backend #

withBaseBackend :: forall backend (m :: Type -> Type) a. HasPersistBackend backend => ReaderT (BaseBackend backend) m a -> ReaderT backend m a #

Run a query against a larger backend by plucking out BaseBackend backend

This is a helper for reusing existing queries when expanding the backend type.

Since: persistent-2.12.0

withCompatibleBackend :: forall sup sub (m :: Type -> Type) a. BackendCompatible sup sub => ReaderT sup m a -> ReaderT sub m a #

Run a query against a compatible backend, by projecting the backend

This is a helper for using queries which run against a specific backend type that your backend is compatible with.

Since: persistent-2.12.0

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

getJust :: forall record backend (m :: Type -> Type). (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 :: forall record backend (m :: Type -> Type). (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

belongsTo :: forall ent1 ent2 backend (m :: Type -> Type). (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 :: forall ent1 ent2 backend (m :: Type -> Type). (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.

insertEntity :: forall e backend (m :: Type -> Type). (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 :: forall record backend (m :: Type -> Type). (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

data SqlBackend #

A SqlBackend represents a handle or connection to a database. It contains functions and values that allow databases to have more optimized implementations, as well as references that benefit performance and sharing.

Instead of using the SqlBackend constructor directly, use the mkSqlBackend function.

A SqlBackend is *not* thread-safe. You should not assume that a SqlBackend can be shared among threads and run concurrent queries. This *will* result in problems. Instead, you should create a Pool SqlBackend, known as a ConnectionPool, and pass that around in multi-threaded applications.

To run actions in the persistent library, you should use the runSqlConn function. If you're using a multithreaded application, use the runSqlPool function.

Instances

Instances details
HasPersistBackend SqlBackend 
Instance details

Defined in Database.Persist.SqlBackend.Internal

Associated Types

type BaseBackend SqlBackend #

IsPersistBackend SqlBackend 
Instance details

Defined in Database.Persist.SqlBackend.Internal

newtype BackendKey SqlBackend 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type BaseBackend SqlBackend 
Instance details

Defined in Database.Persist.SqlBackend.Internal

type Rep (BackendKey SqlBackend) 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.13.3.5-JQO0xSplhu4Dob8Xs9toj2" 'True) (C1 ('MetaCons "SqlBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))

class PersistEntity record => AtLeastOneUniqueKey record where #

This class is used to ensure that functions requring at least one unique key are not called with records that have 0 unique keys. The quasiquoter automatically writes working instances for appropriate entities, and generates TypeError instances for records that have 0 unique keys.

Since: persistent-2.10.0

Methods

requireUniquesP :: record -> NonEmpty (Unique record) #

type MultipleUniqueKeysError ty = ((('Text "The entity " :<>: 'ShowType ty) :<>: 'Text " has multiple unique keys.") :$$: ('Text "The function you are trying to call requires only a single " :<>: 'Text "unique key.")) :$$: (('Text "There is probably a variant of the function with 'By' " :<>: 'Text "appended that will allow you to select a unique key ") :<>: 'Text "for the operation.") #

This is an error message. It is used when an entity has multiple unique keys, and the function expects a single unique key.

Since: persistent-2.10.0

type NoUniqueKeysError ty = (('Text "The entity " :<>: 'ShowType ty) :<>: 'Text " does not have any unique keys.") :$$: ('Text "The function you are trying to call requires a unique key " :<>: 'Text "to be defined on the entity.") #

This is an error message. It is used when writing instances of OnlyOneUniqueKey for an entity that has no unique keys.

Since: persistent-2.10.0

class PersistEntity record => OnlyOneUniqueKey record where #

This class is used to ensure that upsert is only called on records that have a single Unique key. The quasiquoter automatically generates working instances for appropriate records, and generates TypeError instances for records that have 0 or multiple unique keys.

Since: persistent-2.10.0

Methods

onlyUniqueP :: record -> Unique record #

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 :: forall record (m :: Type -> Type). (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 :: forall record (m :: Type -> Type). (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

:: forall record (m :: Type -> Type). (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

:: forall record (m :: Type -> Type). (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

:: forall record (m :: Type -> Type). (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 PersistStoreRead backend => PersistUniqueRead backend #

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.

Minimal complete definition

getBy

onlyOneUniqueDef :: (OnlyOneUniqueKey record, Monad proxy) => proxy record -> UniqueDef #

Given a proxy for a PersistEntity record, this returns the sole UniqueDef for that entity.

Since: persistent-2.13.0.0

insertBy :: forall record backend (m :: Type -> Type). (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 :: forall record backend (m :: Type -> Type). (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 :: forall record backend (m :: Type -> Type). (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.

getByValue :: forall record (m :: Type -> Type) backend. (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 |
+----+------+-----+

replaceUnique :: forall record backend (m :: Type -> Type). (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

checkUnique :: forall record backend (m :: Type -> Type). (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

checkUniqueUpdateable :: forall record backend (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend, PersistUniqueRead backend) => Entity 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 stay unique, and could thus safely be updated. on a conflict returns the conflicting key

This is similar to checkUnique, except it's useful for updating - when the particular entity already exists, it would normally conflict with itself. This variant ignores those conflicts

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

Since: persistent-2.11.0.0

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

Backends supporting conditional write operations

Minimal complete definition

updateWhere, deleteWhere

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

Backends supporting conditional read operations.

Minimal complete definition

selectSourceRes, selectKeysRes, count, exists

Methods

selectSourceRes :: forall record (m1 :: Type -> Type) (m2 :: Type -> Type). (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.

NOTE: This function returns an Acquire and a ConduitM, which implies that it streams from the database. It does not. Please use selectList to simplify the code. If you want streaming behavior, consider persistent-pagination which efficiently chunks a query into ranges, or investigate a backend-specific streaming solution.

selectKeysRes :: forall (m1 :: Type -> Type) (m2 :: Type -> Type) record. (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.

selectKeys :: forall record backend (m :: Type -> Type). (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.

For an example, see selectList.

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 :: forall (m :: Type -> Type). MonadIO m => Key record -> ReaderT backend m () #

Perform cascade-deletion of single database entry.

deleteCascadeWhere :: forall record backend (m :: Type -> Type). (MonadIO m, DeleteCascade record backend, PersistQueryWrite backend) => [Filter record] -> ReaderT backend m () #

Cascade-deletion of entries satisfying given filters.

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.

type IsSqlBackend backend = (IsPersistBackend backend, BaseBackend backend ~ SqlBackend) #

A backend which is a wrapper around SqlBackend.

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.

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

newtype SqlWriteBackend #

An SQL backend which can handle read or write queries

The constructor was exposed in 2.10.0

Instances

Instances details
HasPersistBackend SqlWriteBackend 
Instance details

Defined in Database.Persist.Sql.Types.Internal

Associated Types

type BaseBackend SqlWriteBackend #

IsPersistBackend SqlWriteBackend 
Instance details

Defined in Database.Persist.Sql.Types.Internal

newtype BackendKey SqlWriteBackend 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type BaseBackend SqlWriteBackend 
Instance details

Defined in Database.Persist.Sql.Types.Internal

type Rep (BackendKey SqlWriteBackend) 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlWriteBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.13.3.5-JQO0xSplhu4Dob8Xs9toj2" 'True) (C1 ('MetaCons "SqlWriteBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlWriteBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))

newtype SqlReadBackend #

An SQL backend which can only handle read queries

The constructor was exposed in 2.10.0.

Instances

Instances details
HasPersistBackend SqlReadBackend 
Instance details

Defined in Database.Persist.Sql.Types.Internal

Associated Types

type BaseBackend SqlReadBackend #

IsPersistBackend SqlReadBackend 
Instance details

Defined in Database.Persist.Sql.Types.Internal

newtype BackendKey SqlReadBackend 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type BaseBackend SqlReadBackend 
Instance details

Defined in Database.Persist.Sql.Types.Internal

type Rep (BackendKey SqlReadBackend) 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlReadBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.13.3.5-JQO0xSplhu4Dob8Xs9toj2" 'True) (C1 ('MetaCons "SqlReadBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlReadBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))

writeToUnknown :: forall (m :: Type -> Type) a. Monad m => ReaderT SqlWriteBackend m a -> ReaderT SqlBackend m a #

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

readToWrite :: forall (m :: Type -> Type) a. Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlWriteBackend m a #

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

readToUnknown :: forall (m :: Type -> Type) a. Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlBackend m a #

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

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

Instances details
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 #

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 #

PersistField a => RawSql (Single a) 
Instance details

Defined in Database.Persist.Sql.Class

data ConnectionPoolConfig #

Values to configure a pool of database connections. See Data.Pool for details.

Since: persistent-2.11.0.0

Constructors

ConnectionPoolConfig 

Fields

data ColumnReference #

This value specifies how a field references another table.

Since: persistent-2.11.0.0

Constructors

ColumnReference 

Fields

data Column #

Instances

Instances details
Show Column 
Instance details

Defined in Database.Persist.Sql.Types

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

defaultConnectionPoolConfig :: ConnectionPoolConfig #

Initializes a ConnectionPoolConfig with default values. See the documentation of ConnectionPoolConfig for each field's default value.

Since: persistent-2.11.0.0

data BackendSpecificOverrides #

Record of functions to override the default behavior in mkColumns. It is recommended you initialize this with emptyBackendSpecificOverrides and override the default values, so that as new fields are added, your code still compiles.

For added safety, use the getBackendSpecific* and setBackendSpecific* functions, as a breaking change to the record field labels won't be reflected in a major version bump of the library.

Since: persistent-2.11

getBackendSpecificForeignKeyName :: BackendSpecificOverrides -> Maybe (EntityNameDB -> FieldNameDB -> ConstraintNameDB) #

If the override is defined, then this returns a function that accepts an entity name and field name and provides the ConstraintNameDB for the foreign key constraint.

An abstract accessor for the BackendSpecificOverrides

Since: persistent-2.13.0.0

setBackendSpecificForeignKeyName :: (EntityNameDB -> FieldNameDB -> ConstraintNameDB) -> BackendSpecificOverrides -> BackendSpecificOverrides #

Set the backend's foreign key generation function to this value.

Since: persistent-2.13.0.0

emptyBackendSpecificOverrides :: BackendSpecificOverrides #

Creates an empty BackendSpecificOverrides (i.e. use the default behavior; no overrides)

Since: persistent-2.11

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

Create the list of columns for the given entity.

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

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

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 = PersistLiteralEncoded . toASCIIBytes
  fromPersistValue (PersistLiteralEncoded 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 PersistLiteralEncoded, 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

Instances details
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 Int8 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Int8 -> SqlType #

PersistFieldSql Rational 
Instance details

Defined in Database.Persist.Sql.Class

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 Html 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Html -> SqlType #

PersistFieldSql ByteString 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql OverflowNatural

This type uses the SqlInt64 version, which will exhibit overflow and underflow behavior. Additionally, it permits negative values in the database, which isn't ideal.

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql PersistValue 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql Checkmark 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql Text 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Text -> SqlType #

PersistFieldSql Text 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Text -> SqlType #

PersistFieldSql Day 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Day -> SqlType #

PersistFieldSql UTCTime 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql TimeOfDay 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql Word8 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Word8 -> SqlType #

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 Word 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Word -> 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 #

PersistFieldSql a => PersistFieldSql (Maybe a) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy (Maybe a) -> 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 (Map Text v) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

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

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

Defined in Database.Persist.Sql.Class

Methods

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

newtype EntityWithPrefix (prefix :: Symbol) record #

This newtype wrapper is useful when selecting an entity out of the database and you want to provide a prefix to the table being selected.

Consider this raw SQL query:

SELECT ??
FROM my_long_table_name AS mltn
INNER JOIN other_table AS ot
   ON mltn.some_col = ot.other_col
WHERE ...

We don't want to refer to my_long_table_name every time, so we create an alias. If we want to select it, we have to tell the raw SQL quasi-quoter that we expect the entity to be prefixed with some other name.

We can give the above query a type with this, like:

getStuff :: SqlPersistM [EntityWithPrefix "mltn" MyLongTableName]
getStuff = rawSql queryText []

The EntityWithPrefix bit is a boilerplate newtype wrapper, so you can remove it with unPrefix, like this:

getStuff :: SqlPersistM [Entity MyLongTableName]
getStuff = unPrefix @"mltn" <$> rawSql queryText []

The symbol is a "type application" and requires the TypeApplications@ language extension.

Since: persistent-2.10.5

Constructors

EntityWithPrefix 

Fields

Instances

Instances details
(PersistEntity record, KnownSymbol prefix, PersistEntityBackend record ~ backend, IsPersistBackend backend) => RawSql (EntityWithPrefix prefix record) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> EntityWithPrefix prefix record -> (Int, [Text]) #

rawSqlColCountReason :: EntityWithPrefix prefix record -> String #

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

class RawSql a where #

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

Methods

rawSqlCols :: (Text -> 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

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

Defined in Database.Persist.Sql.Class

Methods

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

rawSqlColCountReason :: Entity record -> String #

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

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

Defined in Database.Persist.Sql.Class

PersistField a => RawSql (Single a) 
Instance details

Defined in Database.Persist.Sql.Class

RawSql a => RawSql (Maybe a)

Since: persistent-1.0.1

Instance details

Defined in Database.Persist.Sql.Class

(PersistEntity record, KnownSymbol prefix, PersistEntityBackend record ~ backend, IsPersistBackend backend) => RawSql (EntityWithPrefix prefix record) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> EntityWithPrefix prefix record -> (Int, [Text]) #

rawSqlColCountReason :: EntityWithPrefix prefix record -> String #

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

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

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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 :: (Text -> 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) #

(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 m) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

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

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

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

(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 m, RawSql n) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

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

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

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

(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 m, RawSql n, RawSql o) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

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

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

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

(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 m, RawSql n, RawSql o, RawSql p) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

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

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

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

(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 m, RawSql n, RawSql o, RawSql p, RawSql q) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

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

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> String #

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

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3, RawSql g3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3, RawSql g3, RawSql h3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3, RawSql g3, RawSql h3, RawSql i3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3) #

(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 m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3, RawSql g3, RawSql h3, RawSql i3, RawSql j3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3, j3)

Since: persistent-2.11.0

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3, j3) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3, j3) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3, j3) #

unPrefix :: forall (prefix :: Symbol) record. EntityWithPrefix prefix record -> Entity record #

A helper function to tell GHC what the EntityWithPrefix prefix should be. This allows you to use a type application to specify the prefix, instead of specifying the etype on the result.

As an example, here's code that uses this:

myQuery :: SqlPersistM [Entity Person]
myQuery = fmap (unPrefix @"p") $ rawSql query []
  where
    query = "SELECT ?? FROM person AS p"

Since: persistent-2.10.5

rawQuery :: forall (m :: Type -> Type) env. (MonadResource m, MonadReader env m, BackendCompatible SqlBackend env) => Text -> [PersistValue] -> ConduitM () [PersistValue] m () #

rawQueryRes :: forall (m1 :: Type -> Type) (m2 :: Type -> Type) env. (MonadIO m1, MonadIO m2, BackendCompatible SqlBackend env) => Text -> [PersistValue] -> ReaderT env m1 (Acquire (ConduitM () [PersistValue] m2 ())) #

rawExecute #

Arguments

:: forall (m :: Type -> Type) backend. (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

:: forall (m :: Type -> Type) backend. (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

:: forall a (m :: Type -> Type) backend. (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)

runSqlPool :: forall backend m a. (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.

This function performs the given action in a transaction. If an exception occurs during the action, then the transaction is rolled back.

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.

runSqlPoolWithIsolation :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> IsolationLevel -> m a #

Like runSqlPool, but supports specifying an isolation level.

Since: persistent-2.9.0

runSqlPoolNoTransaction :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> Maybe IsolationLevel -> m a #

Like runSqlPool, but does not surround the action in a transaction. This action might leave your database in a weird state.

Since: persistent-2.12.0.0

runSqlPoolWithHooks #

Arguments

:: forall backend m a before after onException. (MonadUnliftIO m, BackendCompatible SqlBackend backend) 
=> ReaderT backend m a 
-> Pool backend 
-> Maybe IsolationLevel 
-> (backend -> m before)

Run this action immediately before the action is performed.

-> (backend -> m after)

Run this action immediately after the action is completed.

-> (backend -> SomeException -> m onException)

This action is performed when an exception is received. The exception is provided as a convenience - it is rethrown once this cleanup function is complete.

-> m a 

This function is how runSqlPool and runSqlPoolNoTransaction are defined. In addition to the action to be performed and the Pool of conections to use, we give you the opportunity to provide three actions - initialize, afterwards, and onException.

Since: persistent-2.12.0.0

runSqlPoolWithExtensibleHooks :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> Maybe IsolationLevel -> SqlPoolHooks m backend -> m a #

This function is how runSqlPoolWithHooks is defined.

It's currently the most general function for using a SQL pool.

Since: persistent-2.13.0.0

acquireSqlConn :: (MonadReader backend m, BackendCompatible SqlBackend backend) => m (Acquire backend) #

Starts a new transaction on the connection. When the acquired connection is released the transaction is committed and the connection returned to the pool.

Upon an exception the transaction is rolled back and the connection destroyed.

This is equivalent to runSqlConn but does not incur the MonadUnliftIO constraint, meaning it can be used within, for example, a Conduit pipeline.

Since: persistent-2.10.5

acquireSqlConnWithIsolation :: (MonadReader backend m, BackendCompatible SqlBackend backend) => IsolationLevel -> m (Acquire backend) #

Like acquireSqlConn, but lets you specify an explicit isolation level.

Since: persistent-2.10.5

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

runSqlConnWithIsolation :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> backend -> IsolationLevel -> m a #

Like runSqlConn, but supports specifying an isolation level.

Since: persistent-2.9.0

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

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

withSqlPool #

Arguments

:: forall backend m a. (MonadLoggerIO m, MonadUnliftIO m, BackendCompatible SqlBackend backend) 
=> (LogFunc -> IO backend)

create a new connection

-> Int

connection count

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

withSqlPoolWithConfig #

Arguments

:: forall backend m a. (MonadLoggerIO m, MonadUnliftIO m, BackendCompatible SqlBackend backend) 
=> (LogFunc -> IO backend)

Function to create a new connection

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

Creates a pool of connections to a SQL database which can be used by the Pool backend -> m a function. After the function completes, the connections are destroyed.

Since: persistent-2.11.0.0

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

createSqlPoolWithConfig #

Arguments

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

Function to create a new connection

-> ConnectionPoolConfig 
-> m (Pool backend) 

Creates a pool of connections to a SQL database.

Since: persistent-2.11.0.0

withSqlConn :: forall backend m a. (MonadUnliftIO m, MonadLoggerIO 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}}]

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

withRawQuery :: forall (m :: Type -> Type) a. MonadIO m => Text -> [PersistValue] -> ConduitM [PersistValue] Void IO a -> ReaderT SqlBackend m a #

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

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

getTableName :: forall record (m :: Type -> Type) backend. (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 -> EntityNameDB #

useful for a backend to implement tableName by adding escaping

getFieldName :: forall record typ (m :: Type -> Type) backend. (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

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

useful for a backend to implement fieldName by adding escaping

data FilterTablePrefix #

Used when determining how to prefix a column name in a WHERE clause.

Since: persistent-2.12.1.0

Constructors

PrefixTableName

Prefix the column with the table name. This is useful if the column name might be ambiguous.

Since: persistent-2.12.1.0

PrefixExcluded

Prefix the column name with the EXCLUDED keyword. This is used with the Postgresql backend when doing ON CONFLICT DO UPDATE clauses - see the documentation on upsertWhere and upsertManyWhere.

Since: persistent-2.12.1.0

filterClause #

Arguments

:: PersistEntity val 
=> Maybe FilterTablePrefix

include table name or EXCLUDED

-> SqlBackend 
-> [Filter val] 
-> Text 

Render a [Filter record] into a Text value suitable for inclusion into a SQL query.

Since: persistent-2.12.1.0

filterClauseWithVals #

Arguments

:: PersistEntity val 
=> Maybe FilterTablePrefix

include table name or EXCLUDED

-> SqlBackend 
-> [Filter val] 
-> (Text, [PersistValue]) 

Render a [Filter record] into a Text value suitable for inclusion into a SQL query, as well as the [PersistValue] to properly fill in the ? place holders.

Since: persistent-2.12.1.0

orderClause #

Arguments

:: PersistEntity val 
=> Maybe FilterTablePrefix

include table name or EXCLUDED

-> SqlBackend 
-> [SelectOpt val] 
-> Text 

Render a [SelectOpt record] made up *only* of Asc and Desc constructors into a Text value suitable for inclusion into a SQL query.

Since: persistent-2.13.2.0

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

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

newtype PersistUnsafeMigrationException #

An exception indicating that Persistent refused to run some unsafe migrations. Contains a list of pairs where the Bool tracks whether the migration was unsafe (True means unsafe), and the Sql is the sql statement for the migration.

Since: persistent-2.11.1.0

Instances

Instances details
Exception PersistUnsafeMigrationException 
Instance details

Defined in Database.Persist.Sql.Migration

Show PersistUnsafeMigrationException

This Show instance renders an error message suitable for printing to the console. This is a little dodgy, but since GHC uses Show instances when displaying uncaught exceptions, we have little choice.

Instance details

Defined in Database.Persist.Sql.Migration

type Migration = WriterT [Text] (WriterT CautiousMigration (ReaderT SqlBackend IO)) () #

A Migration is a four level monad stack consisting of:

type CautiousMigration = [(Bool, Sql)] #

A list of SQL operations, marked with a safety flag. If the Bool is True, then the operation is *unsafe* - it might be destructive, or otherwise not idempotent. If the Bool is False, then the operation is *safe*, and can be run repeatedly without issues.

type Sql = Text #

parseMigration :: forall (m :: Type -> Type). (HasCallStack, 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' :: forall (m :: Type -> Type). (HasCallStack, 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 :: forall (m :: Type -> Type). (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m () #

Prints a migration.

showMigration :: forall (m :: Type -> Type). (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m [Text] #

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

getMigration :: forall (m :: Type -> Type). (MonadIO m, HasCallStack) => 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.

runMigration :: forall (m :: Type -> Type). 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 throws a PersistUnsafeMigrationException.

runMigrationQuiet :: forall (m :: Type -> Type). MonadIO m => Migration -> ReaderT SqlBackend m [Text] #

Same as runMigration, but does not report the individual migrations on stderr. Instead it returns a list of the executed SQL commands.

This is a safer/more robust alternative to runMigrationSilent, but may be less silent for some persistent implementations, most notably persistent-postgresql

Since: persistent-2.10.2

runMigrationSilent :: forall (m :: Type -> Type). 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 :: forall (m :: Type -> Type). MonadIO m => Migration -> ReaderT SqlBackend m () #

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

runMigrationUnsafeQuiet :: forall (m :: Type -> Type). (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m [Text] #

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

Since: persistent-2.10.2

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.

reportError :: Text -> Migration #

Report a single error in a Migration.

Since: persistent-2.9.2

reportErrors :: [Text] -> Migration #

Report multiple errors in a Migration.

Since: persistent-2.9.2

addMigration #

Arguments

:: Bool

Is the migration unsafe to run? (eg a destructive or non-idempotent update on the schema). If True, the migration is *unsafe*, and will need to be run manually later. If False, the migration is *safe*, and can be run any number of times.

-> Sql

A Text value representing the command to run on the database.

-> Migration 

Add a migration to the migration plan.

Since: persistent-2.9.2

addMigrations :: CautiousMigration -> Migration #

Add a CautiousMigration (aka a [(Bool, Text)]) to the migration plan.

Since: persistent-2.9.2

runSqlCommand :: SqlPersistT IO () -> Migration #

Run an action against the database during a migration. Can be useful for eg creating Postgres extensions:

runSqlCommand $ rawExecute "CREATE EXTENSION IF NOT EXISTS "uuid-ossp";" []

Since: persistent-2.13.0.0

transactionSave :: forall (m :: Type -> Type). 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

transactionSaveWithIsolation :: forall (m :: Type -> Type). MonadIO m => IsolationLevel -> ReaderT SqlBackend m () #

Commit the current transaction and begin a new one with the specified isolation level.

Since: persistent-2.9.0

transactionUndo :: forall (m :: Type -> Type). 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

transactionUndoWithIsolation :: forall (m :: Type -> Type). MonadIO m => IsolationLevel -> ReaderT SqlBackend m () #

Roll back the current transaction and begin a new one with the specified isolation level.

Since: persistent-2.9.0