persistent-postgresql-2.12.1.1: Backend for the persistent library using postgresql.
Safe HaskellNone
LanguageHaskell2010

Database.Persist.Postgresql

Description

A postgresql backend for persistent.

Synopsis

Documentation

withPostgresqlPool Source #

Arguments

:: (MonadLoggerIO m, MonadUnliftIO m) 
=> ConnectionString

Connection string to the database.

-> Int

Number of connections to be kept open in the pool.

-> (Pool SqlBackend -> m a)

Action to be executed that uses the connection pool.

-> m a 

Create a PostgreSQL connection pool and run the given action. The pool is properly released after the action finishes using it. Note that you should not use the given ConnectionPool outside the action since it may already have been released. The provided action should use runSqlConn and *not* runReaderT because the former brackets the database action with transaction begin/commit.

withPostgresqlPoolWithVersion Source #

Arguments

:: (MonadUnliftIO m, MonadLoggerIO m) 
=> (Connection -> IO (Maybe Double))

Action to perform to get the server version.

-> ConnectionString

Connection string to the database.

-> Int

Number of connections to be kept open in the pool.

-> (Pool SqlBackend -> m a)

Action to be executed that uses the connection pool.

-> m a 

Same as withPostgresPool, but takes a callback for obtaining the server version (to work around an Amazon Redshift bug).

Since: 2.6.2

withPostgresqlConn :: (MonadUnliftIO m, MonadLoggerIO m) => ConnectionString -> (SqlBackend -> m a) -> m a Source #

Same as withPostgresqlPool, but instead of opening a pool of connections, only one connection is opened. The provided action should use runSqlConn and *not* runReaderT because the former brackets the database action with transaction begin/commit.

withPostgresqlConnWithVersion :: (MonadUnliftIO m, MonadLoggerIO m) => (Connection -> IO (Maybe Double)) -> ConnectionString -> (SqlBackend -> m a) -> m a Source #

Same as withPostgresqlConn, but takes a callback for obtaining the server version (to work around an Amazon Redshift bug).

Since: 2.6.2

withPostgresqlPoolWithConf Source #

Arguments

:: (MonadUnliftIO m, MonadLoggerIO m) 
=> PostgresConf

Configuration for connecting to Postgres

-> PostgresConfHooks

Record of callback functions

-> (Pool SqlBackend -> m a)

Action to be executed that uses the connection pool.

-> m a 

Same as withPostgresqlPool, but can be configured with PostgresConf and PostgresConfHooks.

Since: 2.11.0.0

createPostgresqlPool Source #

Arguments

:: (MonadUnliftIO m, MonadLoggerIO m) 
=> ConnectionString

Connection string to the database.

-> Int

Number of connections to be kept open in the pool.

-> m (Pool SqlBackend) 

Create a PostgreSQL connection pool. Note that it's your responsibility to properly close the connection pool when unneeded. Use withPostgresqlPool for an automatic resource control.

createPostgresqlPoolModified Source #

Arguments

:: (MonadUnliftIO m, MonadLoggerIO m) 
=> (Connection -> IO ())

Action to perform after connection is created.

-> ConnectionString

Connection string to the database.

-> Int

Number of connections to be kept open in the pool.

-> m (Pool SqlBackend) 

Same as createPostgresqlPool, but additionally takes a callback function for some connection-specific tweaking to be performed after connection creation. This could be used, for example, to change the schema. For more information, see:

https://groups.google.com/d/msg/yesodweb/qUXrEN_swEo/O0pFwqwQIdcJ

Since: 2.1.3

createPostgresqlPoolModifiedWithVersion Source #

Arguments

:: (MonadUnliftIO m, MonadLoggerIO m) 
=> (Connection -> IO (Maybe Double))

Action to perform to get the server version.

-> (Connection -> IO ())

Action to perform after connection is created.

-> ConnectionString

Connection string to the database.

-> Int

Number of connections to be kept open in the pool.

-> m (Pool SqlBackend) 

Same as other similarly-named functions in this module, but takes callbacks for obtaining the server version (to work around an Amazon Redshift bug) and connection-specific tweaking (to change the schema).

Since: 2.6.2

createPostgresqlPoolWithConf Source #

Arguments

:: (MonadUnliftIO m, MonadLoggerIO m) 
=> PostgresConf

Configuration for connecting to Postgres

-> PostgresConfHooks

Record of callback functions

-> m (Pool SqlBackend) 

Same as createPostgresqlPool, but can be configured with PostgresConf and PostgresConfHooks.

Since: 2.11.0.0

type ConnectionString = ByteString Source #

A libpq connection string. A simple example of connection string would be "host=localhost port=5432 user=test dbname=test password=test". Please read libpq's documentation at https://www.postgresql.org/docs/current/static/libpq-connect.html for more details on how to create such strings.

data HandleUpdateCollision record Source #

This type is used to determine how to update rows using Postgres' INSERT ... ON CONFLICT KEY UPDATE functionality, exposed via upsertWhere and upsertManyWhere in this library.

Since: 2.12.1.0

copyField :: PersistField typ => EntityField record typ -> HandleUpdateCollision record Source #

Copy the field directly from the record.

Since: 2.12.1.0

copyUnlessNull :: PersistField typ => EntityField record (Maybe typ) -> HandleUpdateCollision record Source #

Copy the field into the database only if the value in the corresponding record is non-NULL.

@since 2.12.1.0

copyUnlessEmpty :: (Monoid typ, PersistField typ) => EntityField record typ -> HandleUpdateCollision record Source #

Copy the field into the database only if the value in the corresponding record is non-empty, where "empty" means the Monoid definition for mempty. Useful for Text, String, ByteString, etc.

The resulting HandleUpdateCollision type is useful for the upsertManyWhere function.

@since 2.12.1.0

copyUnlessEq :: PersistField typ => EntityField record typ -> typ -> HandleUpdateCollision record Source #

Copy the field into the database only if the field is not equal to the provided value. This is useful to avoid copying weird nullary data into the database.

The resulting HandleUpdateCollision type is useful for the upsertMany function.

@since 2.12.1.0

excludeNotEqualToOriginal :: (PersistField typ, PersistEntity rec) => EntityField rec typ -> Filter rec Source #

Exclude any record field if it doesn't match the filter record. Used only in upsertWhere and upsertManyWhere

TODO: we could probably make a sum type for the Filter record that's passed into the upsertWhere and upsertManyWhere methods that has similar behavior to the HandleCollisionUpdate type.

Since: 2.12.1.0

data PostgresConf Source #

Information required to connect to a PostgreSQL database using persistent's generic facilities. These values are the same that are given to withPostgresqlPool.

Constructors

PostgresConf 

Fields

Instances

Instances details
Data PostgresConf Source # 
Instance details

Defined in Database.Persist.Postgresql

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PostgresConf -> c PostgresConf #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PostgresConf #

toConstr :: PostgresConf -> Constr #

dataTypeOf :: PostgresConf -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PostgresConf) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PostgresConf) #

gmapT :: (forall b. Data b => b -> b) -> PostgresConf -> PostgresConf #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PostgresConf -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PostgresConf -> r #

gmapQ :: (forall d. Data d => d -> u) -> PostgresConf -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PostgresConf -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PostgresConf -> m PostgresConf #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PostgresConf -> m PostgresConf #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PostgresConf -> m PostgresConf #

Read PostgresConf Source # 
Instance details

Defined in Database.Persist.Postgresql

Show PostgresConf Source # 
Instance details

Defined in Database.Persist.Postgresql

FromJSON PostgresConf Source # 
Instance details

Defined in Database.Persist.Postgresql

PersistConfig PostgresConf Source # 
Instance details

Defined in Database.Persist.Postgresql

type PersistConfigPool PostgresConf Source # 
Instance details

Defined in Database.Persist.Postgresql

type PersistConfigBackend PostgresConf Source # 
Instance details

Defined in Database.Persist.Postgresql

newtype PgInterval Source #

Represent Postgres interval using NominalDiffTime

Since: 2.11.0.0

Constructors

PgInterval 

upsertWhere :: (backend ~ PersistEntityBackend record, PersistEntity record, PersistEntityBackend record ~ SqlBackend, MonadIO m, PersistStore backend, BackendCompatible SqlBackend backend, OnlyOneUniqueKey record) => record -> [Update record] -> [Filter record] -> ReaderT backend m () Source #

Postgres specific upsertWhere. This method does the following: It will insert a record if no matching unique key exists. If a unique key exists, it will update the relevant field with a user-supplied value, however, it will only do this update on a user-supplied condition. For example, here's how this method could be called like such:

upsertWhere record [recordField =. newValue] [recordField /= newValue]

Called thusly, this method will insert a new record (if none exists) OR update a recordField with a new value assuming the condition in the last block is met.

Since: 2.12.1.0

upsertManyWhere Source #

Arguments

:: forall record backend m. (backend ~ PersistEntityBackend record, BackendCompatible SqlBackend backend, PersistEntityBackend record ~ SqlBackend, PersistEntity record, OnlyOneUniqueKey record, MonadIO m) 
=> [record]

A list of the records you want to insert, or update

-> [HandleUpdateCollision record]

A list of the fields you want to copy over.

-> [Update record]

A list of the updates to apply that aren't dependent on the record being inserted.

-> [Filter record]

A filter condition that dictates the scope of the updates

-> ReaderT backend m () 

Postgres specific upsertManyWhere. This method does the following: It will insert a record if no matching unique key exists. If a unique key exists, it will update the relevant field with a user-supplied value, however, it will only do this update on a user-supplied condition. For example, here's how this method could be called like such:

upsertManyWhere [record] [recordField =. newValue] [recordField !=. newValue]

Called thusly, this method will insert a new record (if none exists) OR update a recordField with a new value assuming the condition in the last block is met.

Since: 2.12.1.0

openSimpleConnWithVersion :: (Connection -> IO (Maybe Double)) -> LogFunc -> Connection -> IO SqlBackend Source #

Generate a SqlBackend from a Connection, but takes a callback for obtaining the server version.

Since: 2.9.1

tableName :: PersistEntity record => record -> Text Source #

Get the SQL string for the table that a PeristEntity represents. Useful for raw SQL queries.

fieldName :: PersistEntity record => EntityField record typ -> Text Source #

Get the SQL string for the field that an EntityField represents. Useful for raw SQL queries.

mockMigration :: Migration -> IO () Source #

Mock a migration even when the database is not present. This function performs the same functionality of printMigration with the difference that an actual database is not needed.

data PostgresConfHooks Source #

Hooks for configuring the Persistent/its connection to Postgres

Since: 2.11.0

Constructors

PostgresConfHooks 

Fields

  • pgConfHooksGetServerVersion :: Connection -> IO (NonEmpty Word)

    Function to get the version of Postgres

    The default implementation queries the server with "show server_version". Some variants of Postgres, such as Redshift, don't support showing the version. It's recommended you return a hardcoded version in those cases.

    Since: 2.11.0

  • pgConfHooksAfterCreate :: Connection -> IO ()

    Action to perform after a connection is created.

    Typical uses of this are modifying the connection (e.g. to set the schema) or logging a connection being created.

    The default implementation does nothing.

    Since: 2.11.0

defaultPostgresConfHooks :: PostgresConfHooks Source #

Default settings for PostgresConfHooks. See the individual fields of PostgresConfHooks for the default values.

Since: 2.11.0