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

Safe HaskellNone
LanguageHaskell98

Database.Persist.Sql

Contents

Synopsis

Documentation

type Connection = SqlBackend Source

Deprecated: Please use SqlBackend instead

Deprecated synonym for SqlBackend.

data SqlBackend Source

Constructors

SqlBackend 

Fields

connPrepare :: Text -> IO Statement
 
connInsertSql :: EntityDef -> [PersistValue] -> InsertSqlResult

table name, column names, id name, either 1 or 2 statements to run

connInsertManySql :: Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)

SQL for inserting many rows and returning their primary keys, for backends that support this functioanlity. If Nothing, rows will be inserted one-at-a-time using connInsertSql.

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
 

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

data Statement Source

Constructors

Statement 

Fields

stmtFinalize :: IO ()
 
stmtReset :: IO ()
 
stmtExecute :: [PersistValue] -> IO Int64
 
stmtQuery :: forall m. MonadIO m => [PersistValue] -> Acquire (Source m [PersistValue])
 

type SqlPersist = SqlPersistT Source

Deprecated: Please use SqlPersistT instead

type Sql = Text 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 you could use withStmt, which allows you to do anything you need. However, its API is low-level and you need to parse each row yourself. However, most of your complex queries will have simple results -- some of your entities and maybe a couple of derived columns.

This is where rawSql comes in. Like withStmt, you may issue any SQL query. However, it does all the hard work for you and automatically parses the rows of the result. It may return:

  • An Entity, that which selectList returns. All of your entity's fields are automatically parsed.
  • A Single a, which is a single, raw column of type a. You may use a Haskell type (such as in your entity definitions), for example Single Text or Single Int, or you may get the raw column value with Single 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.

newtype Single a Source

A single column (see rawSql). Any PersistField may be used here, including PersistValue (which does not do any processing).

Constructors

Single 

Fields

unSingle :: a
 

Instances

Eq a => Eq (Single a) Source 
Ord a => Ord (Single a) Source 
Read a => Read (Single a) Source 
Show a => Show (Single a) Source 
PersistField a => RawSql (Single a) Source 

class RawSql a where Source

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

Methods

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.

Instances

RawSql a => RawSql (Maybe a) Source

Since 1.0.1.

(PersistEntity record, (~) * (PersistEntityBackend record) SqlBackend) => RawSql (Entity record) Source 
(PersistEntity a, (~) * (PersistEntityBackend a) SqlBackend) => 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 

runSqlPool :: MonadBaseControl IO m => SqlPersistT m a -> Pool SqlBackend -> 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.

withResourceTimeout Source

Arguments

:: MonadBaseControl IO 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

withSqlPool Source

Arguments

:: (MonadIO m, MonadLogger m, MonadBaseControl IO m) 
=> (LogFunc -> IO SqlBackend)

create a new connection

-> Int

connection count

-> (Pool SqlBackend -> m a) 
-> m a 

runMigrationSilent :: (MonadBaseControl IO 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.

getFieldName :: forall record typ m. (PersistEntity record, PersistEntityBackend record ~ SqlBackend, Monad m) => EntityField record typ -> ReaderT SqlBackend 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. (PersistEntity record, PersistEntityBackend record ~ SqlBackend, Monad m) => record -> ReaderT SqlBackend 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 :: forall record. (PersistEntity record, PersistEntityBackend record ~ SqlBackend) => 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

rawExecute Source

Arguments

:: MonadIO m 
=> Text

SQL statement, possibly with placeholders.

-> [PersistValue]

Values to fill the placeholders.

-> ReaderT SqlBackend m () 

Execute a raw SQL statement

rawExecuteCount Source

Arguments

:: MonadIO m 
=> Text

SQL statement, possibly with placeholders.

-> [PersistValue]

Values to fill the placeholders.

-> ReaderT SqlBackend m Int64 

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

rawSql Source

Arguments

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

deleteWhereCount :: (PersistEntity val, MonadIO m, PersistEntityBackend val ~ SqlBackend) => [Filter val] -> ReaderT SqlBackend 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) => [Filter val] -> [Update val] -> ReaderT SqlBackend 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

Internal

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

Create the list of columns for the given entity.

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

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