persistent-2.8.0: 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.

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, use rawSql. It does all the hard work of automatically parsing 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

Instances

Eq a => Eq (Single a) Source # 

Methods

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

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

Ord a => Ord (Single a) Source # 

Methods

compare :: Single a -> Single a -> Ordering #

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

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

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

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

max :: Single a -> Single a -> Single a #

min :: Single a -> Single a -> Single a #

Read a => Read (Single a) Source # 
Show a => Show (Single a) Source # 

Methods

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

show :: Single a -> String #

showList :: [Single a] -> ShowS #

PersistField a => RawSql (Single a) Source # 

data SqlBackend Source #

Constructors

SqlBackend 

Fields

data Statement Source #

Constructors

Statement 

Fields

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

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 RawSql a where Source #

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

Minimal complete definition

rawSqlCols, rawSqlColCountReason, rawSqlProcessRow

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

Methods

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

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

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

(RawSql a, RawSql b, RawSql c) => RawSql (a, b, c) Source # 

Methods

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

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

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

(RawSql a, RawSql b, RawSql c, RawSql d) => RawSql (a, b, c, d) Source # 

Methods

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

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

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

(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e) => RawSql (a, b, c, d, e) Source # 

Methods

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

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

rawSqlProcessRow :: [PersistValue] -> Either Text (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 # 

Methods

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

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

rawSqlProcessRow :: [PersistValue] -> Either Text (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 # 

Methods

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

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

rawSqlProcessRow :: [PersistValue] -> Either Text (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 # 

Methods

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

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

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

class PersistField a => PersistFieldSql a where Source #

Minimal complete definition

sqlType

Methods

sqlType :: Proxy a -> SqlType Source #

Instances

PersistFieldSql Bool Source # 
PersistFieldSql Double Source # 
PersistFieldSql Int Source # 
PersistFieldSql Int8 Source # 
PersistFieldSql Int16 Source # 
PersistFieldSql Int32 Source # 
PersistFieldSql Int64 Source # 
PersistFieldSql Natural Source # 
PersistFieldSql Rational Source # 
PersistFieldSql Word Source # 
PersistFieldSql Word8 Source # 
PersistFieldSql Word16 Source # 
PersistFieldSql Word32 Source # 
PersistFieldSql Word64 Source # 
PersistFieldSql ByteString Source # 
PersistFieldSql Text Source # 
PersistFieldSql UTCTime Source # 
PersistFieldSql Text Source # 
PersistFieldSql Html Source # 
PersistFieldSql TimeOfDay Source # 
PersistFieldSql Day Source # 
PersistFieldSql PersistValue Source # 
PersistFieldSql Checkmark Source # 
PersistFieldSql [Char] Source # 

Methods

sqlType :: Proxy * [Char] -> SqlType Source #

PersistFieldSql a => PersistFieldSql [a] Source # 

Methods

sqlType :: Proxy * [a] -> SqlType Source #

HasResolution a => PersistFieldSql (Fixed a) Source # 

Methods

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

PersistFieldSql v => PersistFieldSql (IntMap v) Source # 

Methods

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

(Ord a, PersistFieldSql a) => PersistFieldSql (Set a) Source # 

Methods

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

PersistFieldSql a => PersistFieldSql (Vector a) Source # 

Methods

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

(PersistField record, PersistEntity record) => PersistFieldSql (Entity record) Source # 

Methods

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

(PersistFieldSql a, PersistFieldSql b) => PersistFieldSql (a, b) Source # 

Methods

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

PersistFieldSql v => PersistFieldSql (Map Text v) Source # 

Methods

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

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.

withResourceTimeout Source #

Arguments

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

withSqlPool Source #

Arguments

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

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 #

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

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

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

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.

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

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.

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

rawExecute Source #

Arguments

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

SQL statement, possibly with placeholders.

-> [PersistValue]

Values to fill the placeholders.

-> ReaderT backend m () 

Execute a raw SQL statement

rawExecuteCount Source #

Arguments

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

SQL statement, possibly with placeholders.

-> [PersistValue]

Values to fill the placeholders.

-> ReaderT backend m Int64 

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

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

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

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.