squeal-postgresql-0.5.1.0: Squeal PostgreSQL Library

Copyright(c) Eitan Chatav 2017
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Pool

Contents

Description

A MonadPQ for pooled connections.

Synopsis

Pools

newtype PoolPQ (schemas :: SchemasType) m x Source #

PoolPQ schemas should be a drop-in replacement for PQ schemas schemas.

Typical use case would be to create your pool using createConnectionPool and run anything that requires the pool connection with it.

Here's a simplified example:

>>> import Squeal.PostgreSQL
>>> :{
do
  let
    query :: Query_ (Public '[]) () (Only Char)
    query = values_ $ literal 'a' `as` #fromOnly
    session :: PoolPQ (Public '[]) IO Char
    session = do
      result <- runQuery query
      Just (Only chr) <- firstRow result
      return chr
  pool <- createConnectionPool "host=localhost port=5432 dbname=exampledb" 1 0.5 10
  chr <- runPoolPQ session pool
  destroyAllResources pool
  putChar chr
:}
a

Constructors

PoolPQ 

Fields

Instances
MonadUnliftIO io => MonadPQ schemas (PoolPQ schemas io) Source #

MonadPQ instance for PoolPQ.

Instance details

Defined in Squeal.PostgreSQL.Pool

Methods

manipulateParams :: ToParams x params => Manipulation [] schemas params ys -> x -> PoolPQ schemas io (K Result ys) Source #

manipulateParams_ :: ToParams x params => Manipulation [] schemas params [] -> x -> PoolPQ schemas io () Source #

manipulate :: Manipulation [] schemas [] ys -> PoolPQ schemas io (K Result ys) Source #

manipulate_ :: Manipulation [] schemas [] [] -> PoolPQ schemas io () Source #

runQueryParams :: ToParams x params => Query [] [] schemas params ys -> x -> PoolPQ schemas io (K Result ys) Source #

runQuery :: Query [] [] schemas [] ys -> PoolPQ schemas io (K Result ys) Source #

traversePrepared :: (ToParams x params, Traversable list) => Manipulation [] schemas params ys -> list x -> PoolPQ schemas io (list (K Result ys)) Source #

forPrepared :: (ToParams x params, Traversable list) => list x -> Manipulation [] schemas params ys -> PoolPQ schemas io (list (K Result ys)) Source #

traversePrepared_ :: (ToParams x params, Foldable list) => Manipulation [] schemas params [] -> list x -> PoolPQ schemas io () Source #

forPrepared_ :: (ToParams x params, Foldable list) => list x -> Manipulation [] schemas params [] -> PoolPQ schemas io () Source #

liftPQ :: (Connection -> IO a) -> PoolPQ schemas io a Source #

MonadTrans (PoolPQ schemas :: (Type -> Type) -> Type -> Type) Source #

MonadTrans instance for PoolPQ.

Instance details

Defined in Squeal.PostgreSQL.Pool

Methods

lift :: Monad m => m a -> PoolPQ schemas m a #

Monad m => Monad (PoolPQ schemas m) Source #

Monad instance for PoolPQ.

Instance details

Defined in Squeal.PostgreSQL.Pool

Methods

(>>=) :: PoolPQ schemas m a -> (a -> PoolPQ schemas m b) -> PoolPQ schemas m b #

(>>) :: PoolPQ schemas m a -> PoolPQ schemas m b -> PoolPQ schemas m b #

return :: a -> PoolPQ schemas m a #

fail :: String -> PoolPQ schemas m a #

Functor m => Functor (PoolPQ schemas m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Pool

Methods

fmap :: (a -> b) -> PoolPQ schemas m a -> PoolPQ schemas m b #

(<$) :: a -> PoolPQ schemas m b -> PoolPQ schemas m a #

Monad m => MonadFail (PoolPQ schemas m) Source #

MonadFail instance for PoolPQ.

Instance details

Defined in Squeal.PostgreSQL.Pool

Methods

fail :: String -> PoolPQ schemas m a #

Monad m => Applicative (PoolPQ schemas m) Source #

Applicative instance for PoolPQ.

Instance details

Defined in Squeal.PostgreSQL.Pool

Methods

pure :: a -> PoolPQ schemas m a #

(<*>) :: PoolPQ schemas m (a -> b) -> PoolPQ schemas m a -> PoolPQ schemas m b #

liftA2 :: (a -> b -> c) -> PoolPQ schemas m a -> PoolPQ schemas m b -> PoolPQ schemas m c #

(*>) :: PoolPQ schemas m a -> PoolPQ schemas m b -> PoolPQ schemas m b #

(<*) :: PoolPQ schemas m a -> PoolPQ schemas m b -> PoolPQ schemas m a #

MonadIO m => MonadIO (PoolPQ schemas m) Source #

MonadIO instance for PoolPQ.

Instance details

Defined in Squeal.PostgreSQL.Pool

Methods

liftIO :: IO a -> PoolPQ schemas m a #

MonadUnliftIO m => MonadUnliftIO (PoolPQ schemas m) Source #

MonadUnliftIO instance for PoolPQ.

Instance details

Defined in Squeal.PostgreSQL.Pool

Methods

askUnliftIO :: PoolPQ schemas m (UnliftIO (PoolPQ schemas m)) #

withRunInIO :: ((forall a. PoolPQ schemas m a -> IO a) -> IO b) -> PoolPQ schemas m b #

createConnectionPool Source #

Arguments

:: MonadUnliftIO io 
=> ByteString

The passed string can be empty to use all default parameters, or it can contain one or more parameter settings separated by whitespace. Each parameter setting is in the form keyword = value. Spaces around the equal sign are optional. To write an empty value or a value containing spaces, surround it with single quotes, e.g., keyword = 'a value'. Single quotes and backslashes within the value must be escaped with a backslash, i.e., ' and .

-> Int

The number of stripes (distinct sub-pools) to maintain. The smallest acceptable value is 1.

-> NominalDiffTime

Amount of time for which an unused connection is kept open. The smallest acceptable value is 0.5 seconds. The elapsed time before destroying a connection may be a little longer than requested, as the reaper thread wakes at 1-second intervals.

-> Int

Maximum number of connections to keep open per stripe. The smallest acceptable value is 1. Requests for connections will block if this limit is reached on a single stripe, even if other stripes have idle connections available.

-> io (Pool (K Connection schemas)) 

Create a striped pool of connections. Although the garbage collector will destroy all idle connections when the pool is garbage collected it's recommended to manually destroyAllResources when you're done with the pool so that the connections are freed up as soon as possible.

type Pool = Pool #