Safe Haskell | None |
---|---|
Language | Haskell98 |
- type Connection = SqlBackend
- data Column = Column {}
- data PersistentSqlException
- type SqlPersistT = ReaderT SqlBackend
- type SqlPersist = SqlPersistT
- type SqlPersistM = SqlPersistT (NoLoggingT (ResourceT IO))
- type Sql = Text
- type CautiousMigration = [(Bool, Sql)]
- type Migration = WriterT [Text] (WriterT CautiousMigration (ReaderT SqlBackend IO)) ()
- type ConnectionPool = Pool SqlBackend
- newtype Single a = Single {
- unSingle :: a
- data SqlBackend = SqlBackend {
- connPrepare :: Text -> IO Statement
- connInsertSql :: EntityDef -> [PersistValue] -> InsertSqlResult
- connInsertManySql :: Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
- connUpsertSql :: Maybe (EntityDef -> Text -> Text)
- connPutManySql :: Maybe (EntityDef -> Int -> Text)
- connStmtMap :: IORef (Map Text Statement)
- connClose :: IO ()
- connMigrateSql :: [EntityDef] -> (Text -> IO Statement) -> EntityDef -> IO (Either [Text] [(Bool, Text)])
- connBegin :: (Text -> IO Statement) -> IO ()
- connCommit :: (Text -> IO Statement) -> IO ()
- connRollback :: (Text -> IO Statement) -> IO ()
- connEscapeName :: DBName -> Text
- connNoLimit :: Text
- connRDBMS :: Text
- connLimitOffset :: (Int, Int) -> Bool -> Text -> Text
- connLogFunc :: LogFunc
- connMaxParams :: Maybe Int
- data SqlReadBackend
- data SqlWriteBackend
- data Statement = Statement {
- stmtFinalize :: IO ()
- stmtReset :: IO ()
- stmtExecute :: [PersistValue] -> IO Int64
- stmtQuery :: forall m. MonadIO m => [PersistValue] -> Acquire (ConduitM () [PersistValue] m ())
- type LogFunc = Loc -> LogSource -> LogLevel -> LogStr -> IO ()
- data InsertSqlResult
- readToUnknown :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlBackend m a
- readToWrite :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlWriteBackend m a
- writeToUnknown :: Monad m => ReaderT SqlWriteBackend m a -> ReaderT SqlBackend m a
- type SqlBackendCanRead backend = (BackendCompatible SqlBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend)
- type SqlBackendCanWrite backend = (SqlBackendCanRead backend, PersistQueryWrite backend, PersistStoreWrite backend, PersistUniqueWrite backend)
- type SqlReadT m a = forall backend. SqlBackendCanRead backend => ReaderT backend m a
- type SqlWriteT m a = forall backend. SqlBackendCanWrite backend => ReaderT backend m a
- type IsSqlBackend backend = (IsPersistBackend backend, BaseBackend backend ~ SqlBackend)
- class RawSql a where
- class PersistField a => PersistFieldSql a where
- runSqlPool :: (MonadUnliftIO m, IsSqlBackend backend) => ReaderT backend m a -> Pool backend -> m a
- withResourceTimeout :: forall a m b. MonadUnliftIO m => Int -> Pool a -> (a -> m b) -> m (Maybe b)
- runSqlConn :: (MonadUnliftIO m, IsSqlBackend backend) => ReaderT backend m a -> backend -> m a
- runSqlPersistM :: IsSqlBackend backend => ReaderT backend (NoLoggingT (ResourceT IO)) a -> backend -> IO a
- runSqlPersistMPool :: IsSqlBackend backend => ReaderT backend (NoLoggingT (ResourceT IO)) a -> Pool backend -> IO a
- liftSqlPersistMPool :: (MonadIO m, IsSqlBackend backend) => ReaderT backend (NoLoggingT (ResourceT IO)) a -> Pool backend -> m a
- withSqlPool :: (MonadLogger m, MonadUnliftIO m, IsSqlBackend backend) => (LogFunc -> IO backend) -> Int -> (Pool backend -> m a) -> m a
- createSqlPool :: (MonadLogger m, MonadUnliftIO m, IsSqlBackend backend) => (LogFunc -> IO backend) -> Int -> m (Pool backend)
- askLogFunc :: forall m. (MonadUnliftIO m, MonadLogger m) => m LogFunc
- withSqlConn :: (MonadUnliftIO m, MonadLogger m, IsSqlBackend backend) => (LogFunc -> IO backend) -> (backend -> m a) -> m a
- close' :: IsSqlBackend backend => backend -> IO ()
- parseMigration :: MonadIO m => Migration -> ReaderT SqlBackend m (Either [Text] CautiousMigration)
- parseMigration' :: MonadIO m => Migration -> ReaderT SqlBackend m CautiousMigration
- printMigration :: MonadIO m => Migration -> ReaderT SqlBackend m ()
- showMigration :: MonadIO m => Migration -> ReaderT SqlBackend m [Text]
- getMigration :: MonadIO m => Migration -> ReaderT SqlBackend m [Sql]
- runMigration :: MonadIO m => Migration -> ReaderT SqlBackend m ()
- runMigrationSilent :: (MonadUnliftIO m, MonadIO m) => Migration -> ReaderT SqlBackend m [Text]
- runMigrationUnsafe :: MonadIO m => Migration -> ReaderT SqlBackend m ()
- migrate :: [EntityDef] -> EntityDef -> Migration
- module Database.Persist
- withRawQuery :: 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
- getFieldName :: forall record typ m backend. (PersistEntity record, PersistEntityBackend record ~ SqlBackend, IsSqlBackend backend, Monad m) => EntityField record typ -> ReaderT backend m Text
- getTableName :: forall record m backend. (PersistEntity record, PersistEntityBackend record ~ SqlBackend, IsSqlBackend backend, Monad m) => record -> ReaderT backend m Text
- tableDBName :: PersistEntity record => record -> DBName
- fieldDBName :: forall record typ. PersistEntity record => EntityField record typ -> DBName
- rawQuery :: (MonadResource m, MonadReader env m, HasPersistBackend env, BaseBackend env ~ SqlBackend) => Text -> [PersistValue] -> ConduitM () [PersistValue] m ()
- rawQueryRes :: (MonadIO m1, MonadIO m2, IsSqlBackend env) => Text -> [PersistValue] -> ReaderT env m1 (Acquire (ConduitM () [PersistValue] m2 ()))
- rawExecute :: (MonadIO m, BackendCompatible SqlBackend backend) => Text -> [PersistValue] -> ReaderT backend m ()
- rawExecuteCount :: (MonadIO m, BackendCompatible SqlBackend backend) => Text -> [PersistValue] -> ReaderT backend m Int64
- rawSql :: (RawSql a, MonadIO m) => Text -> [PersistValue] -> ReaderT SqlBackend m [a]
- sqlQQ :: QuasiQuoter
- executeQQ :: QuasiQuoter
- deleteWhereCount :: (PersistEntity val, MonadIO m, PersistEntityBackend val ~ SqlBackend, IsSqlBackend backend) => [Filter val] -> ReaderT backend m Int64
- updateWhereCount :: (PersistEntity val, MonadIO m, SqlBackend ~ PersistEntityBackend val, IsSqlBackend backend) => [Filter val] -> [Update val] -> ReaderT backend m Int64
- transactionSave :: MonadIO m => ReaderT SqlBackend m ()
- transactionUndo :: MonadIO m => ReaderT SqlBackend m ()
- getStmtConn :: SqlBackend -> Text -> IO Statement
- mkColumns :: [EntityDef] -> EntityDef -> ([Column], [UniqueDef], [ForeignDef])
- defaultAttribute :: [Attr] -> Maybe Text
- decorateSQLWithLimitOffset :: Text -> (Int, Int) -> Bool -> Text -> Text
Documentation
type Connection = SqlBackend Source #
Deprecated: Please use SqlBackend instead
Deprecated synonym for SqlBackend
.
type SqlPersistT = ReaderT SqlBackend Source #
type SqlPersist = SqlPersistT Source #
Deprecated: Please use SqlPersistT instead
type SqlPersistM = SqlPersistT (NoLoggingT (ResourceT IO)) Source #
type CautiousMigration = [(Bool, Sql)] Source #
type Migration = WriterT [Text] (WriterT CautiousMigration (ReaderT SqlBackend IO)) () Source #
type ConnectionPool = Pool SqlBackend Source #
Although it covers most of the useful cases, persistent
's
API may not be enough for some of your tasks. May be you need
some complex JOIN
query, or a database-specific command
needs to be issued.
To issue raw SQL queries, use rawSql
. It does all the hard work of
automatically parsing the rows of the result. It may return:
- An
Entity
, that whichselectList
returns. All of your entity's fields are automatically parsed. - A
, which is a single, raw column of typeSingle
aa
. You may use a Haskell type (such as in your entity definitions), for exampleSingle Text
orSingle Int
, or you may get the raw column value withSingle
.PersistValue
- A tuple combining any of these (including other tuples). Using tuples allows you to return many entities in one query.
The only difference between issuing SQL queries with rawSql
and using other means is that we have an entity selection
placeholder, the double question mark ??
. It must be
used whenever you want to SELECT
an Entity
from your
query. Here's a sample SQL query sampleStmt
that may be
issued:
SELECT ??, ?? FROM "Person", "Likes", "Object" WHERE "Person".id = "Likes"."personId" AND "Object".id = "Likes"."objectId" AND "Person".name LIKE ?
To use that query, you could say
do results <- rawSql
sampleStmt ["%Luke%"]
forM_ results $
\( Entity personKey person
, Entity objectKey object
) -> do ...
Note that rawSql
knows how to replace the double question
marks ??
because of the type of the results
.
A single column (see rawSql
). Any PersistField
may be
used here, including PersistValue
(which does not do any
processing).
data SqlBackend Source #
SqlBackend | |
|
data SqlReadBackend Source #
An SQL backend which can only handle read queries
data SqlWriteBackend Source #
An SQL backend which can handle read or write queries
Statement | |
|
readToUnknown :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlBackend m a Source #
Useful for running a read query against a backend with unknown capabilities.
readToWrite :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlWriteBackend m a Source #
Useful for running a read query against a backend with read and write capabilities.
writeToUnknown :: Monad m => ReaderT SqlWriteBackend m a -> ReaderT SqlBackend m a Source #
Useful for running a write query against an untagged backend with unknown capabilities.
type SqlBackendCanRead backend = (BackendCompatible SqlBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend) Source #
A constraint synonym which witnesses that a backend is SQL and can run read queries.
type SqlBackendCanWrite backend = (SqlBackendCanRead backend, PersistQueryWrite backend, PersistStoreWrite backend, PersistUniqueWrite backend) Source #
A constraint synonym which witnesses that a backend is SQL and can run read and write queries.
type SqlReadT m a = forall backend. SqlBackendCanRead backend => ReaderT backend m a Source #
Like SqlPersistT
but compatible with any SQL backend which can handle read queries.
type SqlWriteT m a = forall backend. SqlBackendCanWrite backend => ReaderT backend m a Source #
Like SqlPersistT
but compatible with any SQL backend which can handle read and write queries.
type IsSqlBackend backend = (IsPersistBackend backend, BaseBackend backend ~ SqlBackend) Source #
A backend which is a wrapper around SqlBackend
.
Class for data types that may be retrived from a rawSql
query.
rawSqlCols :: (DBName -> Text) -> a -> (Int, [Text]) Source #
Number of columns that this data type needs and the list
of substitutions for SELECT
placeholders ??
.
rawSqlColCountReason :: a -> String Source #
A string telling the user why the column count is what it is.
rawSqlProcessRow :: [PersistValue] -> Either Text a Source #
Transform a row of the result into the data type.
RawSql a => RawSql (Maybe a) Source # | Since: 1.0.1 |
(PersistEntity record, (~) * (PersistEntityBackend record) backend, IsPersistBackend backend) => RawSql (Entity record) Source # | |
(PersistEntity a, (~) * (PersistEntityBackend a) backend, IsPersistBackend backend) => RawSql (Key a) Source # | |
PersistField a => RawSql (Single a) Source # | |
(RawSql a, RawSql b) => RawSql (a, b) Source # | |
(RawSql a, RawSql b, RawSql c) => RawSql (a, b, c) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d) => RawSql (a, b, c, d) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e) => RawSql (a, b, c, d, e) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f) => RawSql (a, b, c, d, e, f) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g) => RawSql (a, b, c, d, e, f, g) Source # | |
(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) Source # | |
class PersistField a => PersistFieldSql a where Source #
Tells Persistent what database column type should be used to store a Haskell type.
Examples
Simple Boolean Alternative
data Switch = On | Off deriving (Show, Eq) instancePersistField
Switch wheretoPersistValue
s = case s of On ->PersistBool
True Off ->PersistBool
FalsefromPersistValue
(PersistBool
b) = if b thenRight
On elseRight
OfffromPersistValue
x = Left $ "File.hs: When trying to deserialize a Switch: expected PersistBool, received: " <> T.pack (show x) instancePersistFieldSql
Switch wheresqlType
_ =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 instancePersistField
UUID wheretoPersistValue
=PersistDbSpecific
. toASCIIBytesfromPersistValue
(PersistDbSpecific
uuid) = case fromASCIIBytes uuid ofNothing
->Left
$ "Model/CustomTypes.hs: Failed to deserialize a UUID; received: " <> T.pack (show uuid)Just
uuid' ->Right
uuid'fromPersistValue
x = Left $ "File.hs: When trying to deserialize a UUID: expected PersistDbSpecific, received: "-- > <> T.pack (show x) instancePersistFieldSql
UUID wheresqlType
_ =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}$');
instancePersistFieldSQL
SSN wheresqlType
_ =SqlOther
"ssn"
CREATE TYPE rainbow_color AS ENUM ('red', 'orange', 'yellow', 'green', 'blue', 'indigo', 'violet');
instancePersistFieldSQL
RainbowColor wheresqlType
_ =SqlOther
"rainbow_color"
runSqlPool :: (MonadUnliftIO m, IsSqlBackend backend) => ReaderT backend m a -> Pool backend -> m a Source #
Get a connection from the pool, run the given action, and then return the connection to the pool.
Note: This function previously timed out after 2 seconds, but this behavior was buggy and caused more problems than it solved. Since version 2.1.2, it performs no timeout checks.
:: MonadUnliftIO m | |
=> Int | Timeout period in microseconds |
-> Pool a | |
-> (a -> m b) | |
-> m (Maybe b) |
Like withResource
, but times out the operation if resource
allocation does not complete within the given timeout period.
Since: 2.0.0
runSqlConn :: (MonadUnliftIO m, IsSqlBackend backend) => ReaderT backend m a -> backend -> m a Source #
runSqlPersistM :: IsSqlBackend backend => ReaderT backend (NoLoggingT (ResourceT IO)) a -> backend -> IO a Source #
runSqlPersistMPool :: IsSqlBackend backend => ReaderT backend (NoLoggingT (ResourceT IO)) a -> Pool backend -> IO a Source #
liftSqlPersistMPool :: (MonadIO m, IsSqlBackend backend) => ReaderT backend (NoLoggingT (ResourceT IO)) a -> Pool backend -> m a Source #
:: (MonadLogger m, MonadUnliftIO m, IsSqlBackend backend) | |
=> (LogFunc -> IO backend) | create a new connection |
-> Int | connection count |
-> (Pool backend -> m a) | |
-> m a |
createSqlPool :: (MonadLogger m, MonadUnliftIO m, IsSqlBackend backend) => (LogFunc -> IO backend) -> Int -> m (Pool backend) Source #
askLogFunc :: forall m. (MonadUnliftIO m, MonadLogger m) => m LogFunc Source #
withSqlConn :: (MonadUnliftIO m, MonadLogger m, IsSqlBackend backend) => (LogFunc -> IO backend) -> (backend -> m a) -> m a Source #
close' :: IsSqlBackend backend => backend -> IO () Source #
parseMigration :: MonadIO m => Migration -> ReaderT SqlBackend m (Either [Text] CautiousMigration) Source #
Given a Migration
, this parses it and returns either a list of
errors associated with the migration or a list of migrations to do.
parseMigration' :: MonadIO m => Migration -> ReaderT SqlBackend m CautiousMigration Source #
Like parseMigration
, but instead of returning the value in an
Either
value, it calls error
on the error values.
printMigration :: MonadIO m => Migration -> ReaderT SqlBackend m () Source #
Prints a migration.
showMigration :: MonadIO m => Migration -> ReaderT SqlBackend m [Text] Source #
getMigration :: MonadIO m => Migration -> ReaderT SqlBackend m [Sql] Source #
runMigration :: MonadIO m => Migration -> ReaderT SqlBackend m () Source #
Runs a migration. If the migration fails to parse or if any of the
migrations are unsafe, then this calls error
to halt the program.
runMigrationSilent :: (MonadUnliftIO m, MonadIO m) => Migration -> ReaderT SqlBackend m [Text] Source #
Same as runMigration
, but returns a list of the SQL commands executed
instead of printing them to stderr.
runMigrationUnsafe :: MonadIO m => Migration -> ReaderT SqlBackend m () Source #
Like runMigration
, but this will perform the unsafe database
migrations instead of erroring out.
module Database.Persist
withRawQuery :: MonadIO m => Text -> [PersistValue] -> ConduitM [PersistValue] Void IO a -> ReaderT SqlBackend m a Source #
toSqlKey :: ToBackendKey SqlBackend record => Int64 -> Key record Source #
fromSqlKey :: ToBackendKey SqlBackend record => Key record -> Int64 Source #
getFieldName :: forall record typ m backend. (PersistEntity record, PersistEntityBackend record ~ SqlBackend, IsSqlBackend backend, Monad m) => EntityField record typ -> ReaderT backend m Text Source #
get the SQL string for the field that an EntityField represents Useful for raw SQL queries
Your backend may provide a more convenient fieldName function which does not operate in a Monad
getTableName :: forall record m backend. (PersistEntity record, PersistEntityBackend record ~ SqlBackend, IsSqlBackend backend, Monad m) => record -> ReaderT backend m Text Source #
get the SQL string for the table that a PeristEntity represents Useful for raw SQL queries
Your backend may provide a more convenient tableName function which does not operate in a Monad
tableDBName :: PersistEntity record => record -> DBName Source #
useful for a backend to implement tableName by adding escaping
fieldDBName :: forall record typ. PersistEntity record => EntityField record typ -> DBName Source #
useful for a backend to implement fieldName by adding escaping
rawQuery :: (MonadResource m, MonadReader env m, HasPersistBackend env, BaseBackend env ~ SqlBackend) => Text -> [PersistValue] -> ConduitM () [PersistValue] m () Source #
rawQueryRes :: (MonadIO m1, MonadIO m2, IsSqlBackend env) => Text -> [PersistValue] -> ReaderT env m1 (Acquire (ConduitM () [PersistValue] m2 ())) Source #
:: (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
:: (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 a, MonadIO m) | |
=> Text | SQL statement, possibly with placeholders. |
-> [PersistValue] | Values to fill the placeholders. |
-> ReaderT SqlBackend m [a] |
Execute a raw SQL statement and return its results as a list.
If you're using Entity
s
(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 Entity
s
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)
sqlQQ :: QuasiQuoter Source #
QuasiQuoter for performing raw sql queries, analoguous to
rawSql
This and the following are convenient QuasiQuoters to perform raw SQL
queries. They each follow the same pattern and are analogous to
the similarly named raw
functions. Neither the quoted function's
behaviour, nor it's return value is altered during the translation and
all documentation provided with it holds.
These QuasiQuoters perform a simple substitution on the query text, that allows value substitutions, table name substitutions as well as column name substitutions.
Here is a small example:
Given the following simple model:
Category rgt Int lft Int
We can now execute this raw query:
let lft = 10 :: Int rgt = 20 :: Int width = rgt - lft in [sqlQQ| DELETE FROM ^{Category} WHERE{CategoryLft} BETWEEN {rgt}; UPDATE category SET
{CategoryRgt} ={CategoryRgt} - #{width} WHERE
{CategoryRgt} > #{rgt}; UPDATE category SET{CategoryLft} =
{CategoryLft} - {rgt}; |]
^{TableName}
looks up the table's name and escapes it, @{ColumnName}
looks up the column's name and properly escapes it and #{value}
inserts
the value via the usual parameter substitution mechanism.
Since: 2.7.2
executeQQ :: QuasiQuoter Source #
Analoguous to rawExecute
Since: 2.7.2
deleteWhereCount :: (PersistEntity val, MonadIO m, PersistEntityBackend val ~ SqlBackend, IsSqlBackend backend) => [Filter val] -> ReaderT backend m Int64 Source #
Same as deleteWhere
, but returns the number of rows affected.
Since: 1.1.5
updateWhereCount :: (PersistEntity val, MonadIO m, SqlBackend ~ PersistEntityBackend val, IsSqlBackend backend) => [Filter val] -> [Update val] -> ReaderT backend m Int64 Source #
Same as updateWhere
, but returns the number of rows affected.
Since: 1.1.5
transactionSave :: MonadIO m => ReaderT SqlBackend m () Source #
Commit the current transaction and begin a new one.
Since: 1.2.0
transactionUndo :: MonadIO m => ReaderT SqlBackend m () Source #
Roll back the current transaction and begin a new one.
Since: 1.2.0
getStmtConn :: SqlBackend -> Text -> IO Statement Source #