persistent-postgresql-2.10.0: Backend for the persistent library using postgresql.

Safe HaskellNone
LanguageHaskell2010

Database.Persist.Postgresql

Description

A postgresql backend for persistent.

Synopsis

Documentation

withPostgresqlPool Source #

Arguments

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

withPostgresqlPoolWithVersion Source #

Arguments

:: (MonadUnliftIO m, MonadLogger 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, MonadLogger m) => ConnectionString -> (SqlBackend -> m a) -> m a Source #

Same as withPostgresqlPool, but instead of opening a pool of connections, only one connection is opened.

withPostgresqlConnWithVersion :: (MonadUnliftIO m, MonadLogger 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

createPostgresqlPool Source #

Arguments

:: (MonadUnliftIO m, MonadLogger 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, MonadLogger 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, MonadLogger 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

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

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.