effectful-opaleye
Safe HaskellNone
LanguageHaskell2010

Effectful.Opaleye

Synopsis

Effect

data Opaleye (a :: Type -> Type) b where Source #

A dynamic effect to perform opaleye operations.

Constructors

RunSelectExplicit :: forall fields haskells (a :: Type -> Type). FromFields fields haskells -> Select fields -> Opaleye a [haskells]

Lifted RunSelectExplicit.

RunSelectFoldExplicit :: forall fields haskells b (a :: Type -> Type). FromFields fields haskells -> Select fields -> b -> (b -> haskells -> a b) -> Opaleye a b

Lifted RunSelectFoldExplicit.

RunInsert :: forall b (a :: Type -> Type). Insert b -> Opaleye a b

Lifted RunInsert.

RunDelete :: forall b (a :: Type -> Type). Delete b -> Opaleye a b

Lifted RunDelete.

RunUpdate :: forall b (a :: Type -> Type). Update b -> Opaleye a b

Lifted RunUpdate.

Instances

Instances details
type DispatchOf Opaleye Source # 
Instance details

Defined in Effectful.Opaleye.Effect

Effectful functions

Select

runSelect :: forall (es :: [Effect]) fields haskells. (HasCallStack, Opaleye :> es, Default FromFields fields haskells) => Select fields -> Eff es [haskells] Source #

Lifted runSelect.

runSelectI :: forall (es :: [Effect]) fields haskells. (HasCallStack, Opaleye :> es, Default (Inferrable FromFields) fields haskells) => Select fields -> Eff es [haskells] Source #

Lifted runSelectI.

runSelectExplicit :: forall fields haskells (es :: [Effect]). (HasCallStack, Opaleye :> es) => FromFields fields haskells -> Select fields -> Eff es [haskells] Source #

Select-fold

runSelectFold :: forall (es :: [Effect]) fields haskells b. (HasCallStack, Opaleye :> es, Default FromFields fields haskells) => Select fields -> b -> (b -> haskells -> Eff es b) -> Eff es b Source #

runSelectFoldExplicit :: forall fields haskells b (es :: [Effect]). (HasCallStack, Opaleye :> es) => FromFields fields haskells -> Select fields -> b -> (b -> haskells -> Eff es b) -> Eff es b Source #

Insert

runInsert :: forall haskells (es :: [Effect]). (HasCallStack, Opaleye :> es) => Insert haskells -> Eff es haskells Source #

Lifted RunInsert.

Delete

runDelete :: forall haskells (es :: [Effect]). (HasCallStack, Opaleye :> es) => Delete haskells -> Eff es haskells Source #

Lifted RunDelete.

Update

runUpdate :: forall haskells (es :: [Effect]). (HasCallStack, Opaleye :> es) => Update haskells -> Eff es haskells Source #

Lifted RunUpdate.

Interpreters

runOpaleyeWithConnection :: forall (es :: [Effect]) a. (HasCallStack, WithConnection :> es, IOE :> es) => Eff (Opaleye ': es) a -> Eff es a Source #

Interpret the Opaleye effect using WithConnection from effectful-postgresql.

If you don't want to use WithConnection, see runOpaleyeConnection.

runOpaleyeWithConnectionCounting :: forall a (es :: [Effect]). (HasCallStack, State SQLOperationCounts :> es, WithConnection :> es, IOE :> es) => Eff (Opaleye ': es) a -> Eff es a Source #

Same as runOpaleyeWithConnection, but we track the number of SQL operations that we perform.

runOpaleyeConnection :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => Connection -> Eff (Opaleye ': es) a -> Eff es a Source #

Interpret the Opaleye effect by simply supplying a Connection

runOpaleyeConnectionCounting :: forall (es :: [Effect]) a. (HasCallStack, State SQLOperationCounts :> es, IOE :> es) => Connection -> Eff (Opaleye ': es) a -> Eff es a Source #

Same as runOpaleyeConnection, but we track the number of SQL operations that we perform.

Counting SQL operations

data SQLOperationCounts Source #

This tracks the number of SQL operations that have been performed in the Opaleye effect, along with which table it was performed on (where possible).

INSERT, DELETE and UPDATE operations act on one table only, so we can tally the number of each that are performed on each table (indexed by a QualifiedIdentifier). SELECT operations can act on multiple tables, so we just track the total number of selects.

If required, SQLOperationCounts can be constructed using Monoid and combined using Semigroup.

We use non-negative Naturals as a tally since a negative number of operations makes no sense.

Instances

Instances details
Monoid SQLOperationCounts Source # 
Instance details

Defined in Effectful.Opaleye.Count

Semigroup SQLOperationCounts Source # 
Instance details

Defined in Effectful.Opaleye.Count

Generic SQLOperationCounts Source # 
Instance details

Defined in Effectful.Opaleye.Count

Associated Types

type Rep SQLOperationCounts 
Instance details

Defined in Effectful.Opaleye.Count

Show SQLOperationCounts Source # 
Instance details

Defined in Effectful.Opaleye.Count

Eq SQLOperationCounts Source # 
Instance details

Defined in Effectful.Opaleye.Count

Pretty SQLOperationCounts Source # 
Instance details

Defined in Effectful.Opaleye.Count

type Rep SQLOperationCounts Source # 
Instance details

Defined in Effectful.Opaleye.Count

withCounts :: forall (es :: [Effect]) a. State SQLOperationCounts :> es => Eff es a -> Eff es (SQLOperationCounts, a) Source #

This allows us to count the number of SQL operations over the course of a sub-operation.

printCounts :: MonadIO m => SQLOperationCounts -> m () Source #

Print an SQLOperationCounts to stdout using prettyCounts. For less verbose output, see printCountsBrief.