Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Connection = Connection {}
- getBackendPidIO :: Connection -> IO BackendPid
- data ConnectionData = ConnectionData {
- cdPtr :: !(Ptr PGconn)
- cdBackendPid :: !BackendPid
- cdStats :: !ConnectionStats
- cdPreparedQueries :: !(IORef (Set Text))
- withConnectionData :: Connection -> String -> (ConnectionData -> IO (ConnectionData, r)) -> IO r
- data ConnectionStats = ConnectionStats {
- statsQueries :: !Int
- statsRows :: !Int
- statsValues :: !Int
- statsParams :: !Int
- data ConnectionSettings = ConnectionSettings {
- csConnInfo :: !Text
- csClientEncoding :: !(Maybe Text)
- csRole :: !(Maybe (RawSQL ()))
- csComposites :: ![Text]
- defaultConnectionSettings :: ConnectionSettings
- newtype ConnectionSourceM m = ConnectionSourceM {
- withConnection :: forall r. (Connection -> m r) -> m r
- newtype ConnectionSource (cs :: [(Type -> Type) -> Constraint]) = ConnectionSource {
- unConnectionSource :: forall m. MkConstraint m cs => ConnectionSourceM m
- simpleSource :: ConnectionSettings -> ConnectionSource [MonadBase IO, MonadMask]
- poolSource :: ConnectionSettings -> (IO Connection -> (Connection -> IO ()) -> PoolConfig Connection) -> IO (ConnectionSource [MonadBase IO, MonadMask])
- connect :: ConnectionSettings -> IO Connection
- disconnect :: Connection -> IO ()
- runQueryIO :: (HasCallStack, IsSQL sql) => Connection -> sql -> IO (Int, ForeignPtr PGresult)
- newtype QueryName = QueryName Text
- runPreparedQueryIO :: (HasCallStack, IsSQL sql) => Connection -> QueryName -> sql -> IO (Int, ForeignPtr PGresult)
Connection
newtype Connection Source #
Wrapper for hiding representation of a connection object.
getBackendPidIO :: Connection -> IO BackendPid Source #
data ConnectionData Source #
Representation of a connection object.
Note: PGconn is not managed with a ForeignPtr because finalizers are broken and at program exit might run even though another thread is inside the relevant withForeignPtr block, executing a safe FFI call (in this case executing an SQL query).
See https://gitlab.haskell.org/ghc/ghc/-/issues/10975 for more info.
ConnectionData | |
|
withConnectionData :: Connection -> String -> (ConnectionData -> IO (ConnectionData, r)) -> IO r Source #
data ConnectionStats Source #
Simple connection statistics.
ConnectionStats | |
|
Instances
Show ConnectionStats Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Connection showsPrec :: Int -> ConnectionStats -> ShowS # show :: ConnectionStats -> String # showList :: [ConnectionStats] -> ShowS # | |
Eq ConnectionStats Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Connection (==) :: ConnectionStats -> ConnectionStats -> Bool # (/=) :: ConnectionStats -> ConnectionStats -> Bool # | |
Ord ConnectionStats Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Connection compare :: ConnectionStats -> ConnectionStats -> Ordering # (<) :: ConnectionStats -> ConnectionStats -> Bool # (<=) :: ConnectionStats -> ConnectionStats -> Bool # (>) :: ConnectionStats -> ConnectionStats -> Bool # (>=) :: ConnectionStats -> ConnectionStats -> Bool # max :: ConnectionStats -> ConnectionStats -> ConnectionStats # min :: ConnectionStats -> ConnectionStats -> ConnectionStats # |
data ConnectionSettings Source #
ConnectionSettings | |
|
Instances
Show ConnectionSettings Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Connection showsPrec :: Int -> ConnectionSettings -> ShowS # show :: ConnectionSettings -> String # showList :: [ConnectionSettings] -> ShowS # | |
Eq ConnectionSettings Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Connection (==) :: ConnectionSettings -> ConnectionSettings -> Bool # (/=) :: ConnectionSettings -> ConnectionSettings -> Bool # | |
Ord ConnectionSettings Source # | |
Defined in Database.PostgreSQL.PQTypes.Internal.Connection compare :: ConnectionSettings -> ConnectionSettings -> Ordering # (<) :: ConnectionSettings -> ConnectionSettings -> Bool # (<=) :: ConnectionSettings -> ConnectionSettings -> Bool # (>) :: ConnectionSettings -> ConnectionSettings -> Bool # (>=) :: ConnectionSettings -> ConnectionSettings -> Bool # max :: ConnectionSettings -> ConnectionSettings -> ConnectionSettings # min :: ConnectionSettings -> ConnectionSettings -> ConnectionSettings # |
defaultConnectionSettings :: ConnectionSettings Source #
Default connection settings. Note that all strings sent to PostgreSQL by the library are encoded as UTF-8, so don't alter client encoding unless you know what you're doing.
newtype ConnectionSourceM m Source #
Database connection supplier.
ConnectionSourceM | |
|
newtype ConnectionSource (cs :: [(Type -> Type) -> Constraint]) Source #
Wrapper for a polymorphic connection source.
ConnectionSource | |
|
simpleSource :: ConnectionSettings -> ConnectionSource [MonadBase IO, MonadMask] Source #
Default connection supplier. It establishes new
database connection each time withConnection
is called.
:: ConnectionSettings | |
-> (IO Connection -> (Connection -> IO ()) -> PoolConfig Connection) | A function for creating the Note: supplied arguments are for creation and destruction of a database connection. |
-> IO (ConnectionSource [MonadBase IO, MonadMask]) |
Pooled source. It uses striped pool from resource-pool
package to cache
established connections and reuse them.
connect :: ConnectionSettings -> IO Connection Source #
Low-level function for connecting to the database. Useful if one wants to implement custom connection source.
Warning: the Connection
needs to be explicitly destroyed with
disconnect
, otherwise there will be a resource leak.
disconnect :: Connection -> IO () Source #
Low-level function for disconnecting from the database. Useful if one wants to implement custom connection source.
Running queries
runQueryIO :: (HasCallStack, IsSQL sql) => Connection -> sql -> IO (Int, ForeignPtr PGresult) Source #
Low-level function for running an SQL query.
Name of a prepared query.
runPreparedQueryIO :: (HasCallStack, IsSQL sql) => Connection -> QueryName -> sql -> IO (Int, ForeignPtr PGresult) Source #
Low-level function for running a prepared SQL query.