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

Safe HaskellNone

Database.Persist.Sql

Contents

Synopsis

Documentation

data Connection Source

Constructors

Connection 

Fields

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

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

connStmtMap :: IORef (Map Text Statement)
 
connClose :: IO ()
 
connMigrateSql :: [EntityDef SqlType] -> (Text -> IO Statement) -> EntityDef SqlType -> 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
 

data Statement Source

Constructors

Statement 

type SqlPersist = SqlPersistTSource

Deprecated: Please use SqlPersistT instead

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) 
Ord a => Ord (Single a) 
Read a => Read (Single a) 
Show a => Show (Single a) 
PersistField a => RawSql (Single a) 

class RawSql a whereSource

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

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

rawSqlProcessRow :: [PersistValue] -> Either Text aSource

Transform a row of the result into the data type.

Instances

RawSql a => RawSql (Maybe a)

Since 1.0.1.

PersistEntity a => RawSql (Entity a) 
PersistField a => RawSql (Single a) 
(RawSql a, RawSql b) => RawSql (a, b) 
(RawSql a, RawSql b, RawSql c) => RawSql (a, b, c) 
(RawSql a, RawSql b, RawSql c, RawSql d) => RawSql (a, b, c, d) 
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e) => RawSql (a, b, c, d, e) 
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f) => RawSql (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) 
(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) 

runSqlPool :: MonadBaseControl IO m => SqlPersistT m a -> Pool Connection -> m aSource

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

withSqlPoolSource

Arguments

:: MonadIO m 
=> IO Connection

create a new connection

-> Int

connection count

-> (Pool Connection -> m a) 
-> m a 

runMigrationSilent :: (MonadBaseControl IO m, MonadSqlPersist m) => Migration m -> m [Text]Source

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

rawSqlSource

Arguments

:: (RawSql a, MonadSqlPersist m, MonadResource m) 
=> Text

SQL statement, possibly with placeholders.

-> [PersistValue]

Values to fill the placeholders.

-> 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, MonadSqlPersist m) => [Filter val] -> m Int64Source

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

Since 1.1.5

updateWhereCount :: (PersistEntity val, MonadSqlPersist m) => [Filter val] -> [Update val] -> m Int64Source

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

Since 1.1.5

transactionSave :: MonadSqlPersist m => m ()Source

Commit the current transaction and begin a new one.

Since 1.2.0

transactionUndo :: MonadSqlPersist m => m ()Source

Roll back the current transaction and begin a new one.

Since 1.2.0

Internal

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

Create the list of columns for the given entity.

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

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