Safe Haskell | None |
---|---|
Language | Haskell2010 |
Effectful.PostgreSQL.Connection
Synopsis
- data WithConnection (a :: Type -> Type) b where
- WithConnection :: forall (a :: Type -> Type) b. (Connection -> a b) -> WithConnection a b
- withConnection :: forall a (es :: [Effect]). (HasCallStack, WithConnection :> es) => (Connection -> Eff es a) -> Eff es a
- runWithConnection :: forall (es :: [(Type -> Type) -> Type -> Type]) a. HasCallStack => Connection -> Eff (WithConnection ': es) a -> Eff es a
- runWithConnectInfo :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => ConnectInfo -> Eff (WithConnection ': es) a -> Eff es a
Effect
data WithConnection (a :: Type -> Type) b where Source #
A dynamic effect that lets us use a database Connection
,
without specifying how that connection is supplied.
For example, we might want to just provide a connection and let the interpreter
use that for the whole procedure (see runWithConnection
).
Or, we might want to create a connection pool which provides connections when the interpreter asks for them (see Effectful.PostgreSQL.Connection.Pool).
Constructors
WithConnection :: forall (a :: Type -> Type) b. (Connection -> a b) -> WithConnection a b | Use a |
Instances
type DispatchOf WithConnection Source # | |
Defined in Effectful.PostgreSQL.Connection |
withConnection :: forall a (es :: [Effect]). (HasCallStack, WithConnection :> es) => (Connection -> Eff es a) -> Eff es a Source #
Perform the operation WithConnection
.
Interpret with a single Connection
runWithConnection :: forall (es :: [(Type -> Type) -> Type -> Type]) a. HasCallStack => Connection -> Eff (WithConnection ': es) a -> Eff es a Source #
Run a WithConnection
effect by simply supplying a Connection
.
The connection will be kept alive for the whole duration of the procedure,
which might not be want you want for long-running processes. If so, see
Effectful.PostgreSQL.Connection.Pool.
runWithConnectInfo :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => ConnectInfo -> Eff (WithConnection ': es) a -> Eff es a Source #
Run a WithConnection
effect using a ConnectInfo
.
withConnect
will handle opening and closing the Connection
.