Safe Haskell | None |
---|---|
Language | Haskell2010 |
Database.Beam.Postgres.Conduit
Contents
Description
More efficient query execution functions for beam-postgres
. These
functions use the conduit
package, to execute beam-postgres
statements in
an arbitrary MonadIO
. These functions may be more efficient for streaming
operations than MonadBeam
.
Synopsis
- streamingRunSelect :: forall (m :: Type -> Type) a. (MonadResource m, MonadFail m, FromBackendRow Postgres a) => Connection -> SqlSelect Postgres a -> ConduitT () a m ()
- runInsert :: forall m (tbl :: (Type -> Type) -> Type). MonadIO m => Connection -> SqlInsert Postgres tbl -> m Int64
- streamingRunInsertReturning :: forall (m :: Type -> Type) a. (MonadResource m, MonadFail m, FromBackendRow Postgres a) => Connection -> PgInsertReturning a -> ConduitT () a m ()
- runUpdate :: forall m (tbl :: (Type -> Type) -> Type). MonadIO m => Connection -> SqlUpdate Postgres tbl -> m Int64
- streamingRunUpdateReturning :: forall (m :: Type -> Type) a. (MonadResource m, MonadFail m, FromBackendRow Postgres a) => Connection -> PgUpdateReturning a -> ConduitT () a m ()
- runDelete :: forall m (tbl :: (Type -> Type) -> Type). MonadIO m => Connection -> SqlDelete Postgres tbl -> m Int64
- streamingRunDeleteReturning :: forall (m :: Type -> Type) a. (MonadResource m, MonadFail m, FromBackendRow Postgres a) => Connection -> PgDeleteReturning a -> ConduitT () a m ()
- executeStatement :: MonadIO m => Connection -> PgSyntax -> m Int64
- streamingRunQueryReturning :: forall (m :: Type -> Type) r. (MonadResource m, MonadFail m, FromBackendRow Postgres r) => Connection -> PgSyntax -> ConduitT () r m ()
- runSelect :: (MonadIO m, MonadFail m, MonadBaseControl IO m, FromBackendRow Postgres a) => Connection -> SqlSelect Postgres a -> (ConduitT () a m () -> m b) -> m b
- runInsertReturning :: (MonadIO m, MonadFail m, MonadBaseControl IO m, FromBackendRow Postgres a) => Connection -> PgInsertReturning a -> (ConduitT () a m () -> m b) -> m b
- runUpdateReturning :: (MonadIO m, MonadFail m, MonadBaseControl IO m, FromBackendRow Postgres a) => Connection -> PgUpdateReturning a -> (ConduitT () a m () -> m b) -> m b
- runDeleteReturning :: (MonadIO m, MonadFail m, MonadBaseControl IO m, FromBackendRow Postgres a) => Connection -> PgDeleteReturning a -> (ConduitT () a m () -> m b) -> m b
- runQueryReturning :: (MonadIO m, MonadFail m, MonadBaseControl IO m, Functor m, FromBackendRow Postgres r) => Connection -> PgSyntax -> (ConduitT () r m () -> m b) -> m b
Documentation
streamingRunSelect :: forall (m :: Type -> Type) a. (MonadResource m, MonadFail m, FromBackendRow Postgres a) => Connection -> SqlSelect Postgres a -> ConduitT () a m () Source #
Run a PostgreSQL SELECT
statement in any MonadResource
.
runInsert :: forall m (tbl :: (Type -> Type) -> Type). MonadIO m => Connection -> SqlInsert Postgres tbl -> m Int64 Source #
Run a PostgreSQL INSERT
statement in any MonadIO
. Returns the number of
rows affected.
streamingRunInsertReturning :: forall (m :: Type -> Type) a. (MonadResource m, MonadFail m, FromBackendRow Postgres a) => Connection -> PgInsertReturning a -> ConduitT () a m () Source #
Run a PostgreSQL INSERT ... RETURNING ...
statement in any MonadResource
and
get a Source
of the newly inserted rows.
runUpdate :: forall m (tbl :: (Type -> Type) -> Type). MonadIO m => Connection -> SqlUpdate Postgres tbl -> m Int64 Source #
Run a PostgreSQL UPDATE
statement in any MonadIO
. Returns the number of
rows affected.
streamingRunUpdateReturning :: forall (m :: Type -> Type) a. (MonadResource m, MonadFail m, FromBackendRow Postgres a) => Connection -> PgUpdateReturning a -> ConduitT () a m () Source #
Run a PostgreSQL UPDATE ... RETURNING ...
statement in any MonadResource
and
get a Source
of the newly updated rows.
runDelete :: forall m (tbl :: (Type -> Type) -> Type). MonadIO m => Connection -> SqlDelete Postgres tbl -> m Int64 Source #
Run a PostgreSQL DELETE
statement in any MonadIO
. Returns the number of
rows affected.
streamingRunDeleteReturning :: forall (m :: Type -> Type) a. (MonadResource m, MonadFail m, FromBackendRow Postgres a) => Connection -> PgDeleteReturning a -> ConduitT () a m () Source #
Run a PostgreSQl DELETE ... RETURNING ...
statement in any
MonadResource
and get a Source
of the deleted rows.
executeStatement :: MonadIO m => Connection -> PgSyntax -> m Int64 Source #
Run any DML statement. Return the number of rows affected
streamingRunQueryReturning :: forall (m :: Type -> Type) r. (MonadResource m, MonadFail m, FromBackendRow Postgres r) => Connection -> PgSyntax -> ConduitT () r m () Source #
Runs any query that returns a set of values
Deprecated streaming variants
runSelect :: (MonadIO m, MonadFail m, MonadBaseControl IO m, FromBackendRow Postgres a) => Connection -> SqlSelect Postgres a -> (ConduitT () a m () -> m b) -> m b Source #
Deprecated: Use streamingRunSelect
Run a PostgreSQL SELECT
statement in any MonadIO
.
runInsertReturning :: (MonadIO m, MonadFail m, MonadBaseControl IO m, FromBackendRow Postgres a) => Connection -> PgInsertReturning a -> (ConduitT () a m () -> m b) -> m b Source #
runUpdateReturning :: (MonadIO m, MonadFail m, MonadBaseControl IO m, FromBackendRow Postgres a) => Connection -> PgUpdateReturning a -> (ConduitT () a m () -> m b) -> m b Source #
runDeleteReturning :: (MonadIO m, MonadFail m, MonadBaseControl IO m, FromBackendRow Postgres a) => Connection -> PgDeleteReturning a -> (ConduitT () a m () -> m b) -> m b Source #
runQueryReturning :: (MonadIO m, MonadFail m, MonadBaseControl IO m, Functor m, FromBackendRow Postgres r) => Connection -> PgSyntax -> (ConduitT () r m () -> m b) -> m b Source #
Deprecated: Use streamingRunQueryReturning
Runs any query that returns a set of values