squeal-postgresql-0.9.1.3: Squeal PostgreSQL Library
Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Squeal.PostgreSQL.Session.Statement

Description

A top-level Statement type wraps a Query or Manipulation together with an EncodeParams and a DecodeRow.

Synopsis

Statement

data Statement db x y where Source #

A Statement consists of a Manipulation or a Query that can be run in a MonadPQ.

Constructors

Manipulation

Constructor for a data manipulation language Statement

Fields

Query

Constructor for a structured query language Statement

Fields

Instances

Instances details
Profunctor (Statement db) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

dimap :: (a -> b) -> (c -> d) -> Statement db b c -> Statement db a d #

lmap :: (a -> b) -> Statement db b c -> Statement db a c #

rmap :: (b -> c) -> Statement db a b -> Statement db a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Statement db a b -> Statement db a c #

(.#) :: forall a b c q. Coercible b a => Statement db b c -> q a b -> Statement db a c #

Functor (Statement db x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

fmap :: (a -> b) -> Statement db x a -> Statement db x b #

(<$) :: a -> Statement db x b -> Statement db x a #

RenderSQL (Statement db x y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

renderSQL :: Statement db x y -> ByteString Source #

query Source #

Arguments

:: (GenericParams db params x xs, GenericRow row y ys) 
=> Query '[] '[] db params row

select, values, ...

-> Statement db x y 

Smart constructor for a structured query language Statement

manipulation Source #

Arguments

:: (GenericParams db params x xs, GenericRow row y ys) 
=> Manipulation '[] db params row

insertInto, update, or deleteFrom, ...

-> Statement db x y 

Smart constructor for a data manipulation language Statement

Prepared

data Prepared m x y Source #

prepare and prepare_ create a Prepared statement. A Prepared statement is a server-side object that can be used to optimize performance. When prepare or prepare_ is executed, the specified Statement is parsed, analyzed, and rewritten.

When the runPrepared command is subsequently issued, the Prepared statement is planned and executed. This division of labor avoids repetitive parse analysis work, while allowing the execution plan to depend on the specific parameter values supplied.

Prepared statements only last for the duration of the current database session. Prepared statements can be manually cleaned up using the deallocate command.

Constructors

Prepared 

Fields

  • runPrepared :: x -> m y

    execute a prepared statement

  • deallocate :: m ()

    manually clean up a prepared statement

Instances

Instances details
Monad m => Category (Prepared m :: Type -> Type -> Type) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

id :: forall (a :: k). Prepared m a a #

(.) :: forall (b :: k) (c :: k) (a :: k). Prepared m b c -> Prepared m a b -> Prepared m a c #

Generic1 (Prepared m x :: Type -> Type) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Associated Types

type Rep1 (Prepared m x) :: k -> Type #

Methods

from1 :: forall (a :: k). Prepared m x a -> Rep1 (Prepared m x) a #

to1 :: forall (a :: k). Rep1 (Prepared m x) a -> Prepared m x a #

Monad m => Arrow (Prepared m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

arr :: (b -> c) -> Prepared m b c #

first :: Prepared m b c -> Prepared m (b, d) (c, d) #

second :: Prepared m b c -> Prepared m (d, b) (d, c) #

(***) :: Prepared m b c -> Prepared m b' c' -> Prepared m (b, b') (c, c') #

(&&&) :: Prepared m b c -> Prepared m b c' -> Prepared m b (c, c') #

Monad m => ArrowChoice (Prepared m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

left :: Prepared m b c -> Prepared m (Either b d) (Either c d) #

right :: Prepared m b c -> Prepared m (Either d b) (Either d c) #

(+++) :: Prepared m b c -> Prepared m b' c' -> Prepared m (Either b b') (Either c c') #

(|||) :: Prepared m b d -> Prepared m c d -> Prepared m (Either b c) d #

MonadFix m => ArrowLoop (Prepared m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

loop :: Prepared m (b, d) (c, d) -> Prepared m b c #

MonadPlus m => ArrowPlus (Prepared m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

(<+>) :: Prepared m b c -> Prepared m b c -> Prepared m b c #

MonadPlus m => ArrowZero (Prepared m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

zeroArrow :: Prepared m b c #

Monad m => Choice (Prepared m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

left' :: Prepared m a b -> Prepared m (Either a c) (Either b c) #

right' :: Prepared m a b -> Prepared m (Either c a) (Either c b) #

MonadFix m => Costrong (Prepared m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

unfirst :: Prepared m (a, d) (b, d) -> Prepared m a b #

unsecond :: Prepared m (d, a) (d, b) -> Prepared m a b #

Monad m => Strong (Prepared m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

first' :: Prepared m a b -> Prepared m (a, c) (b, c) #

second' :: Prepared m a b -> Prepared m (c, a) (c, b) #

Monad m => Traversing (Prepared m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

traverse' :: Traversable f => Prepared m a b -> Prepared m (f a) (f b) #

wander :: (forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t) -> Prepared m a b -> Prepared m s t #

Functor m => Profunctor (Prepared m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

dimap :: (a -> b) -> (c -> d) -> Prepared m b c -> Prepared m a d #

lmap :: (a -> b) -> Prepared m b c -> Prepared m a c #

rmap :: (b -> c) -> Prepared m a b -> Prepared m a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Prepared m a b -> Prepared m a c #

(.#) :: forall a b c q. Coercible b a => Prepared m b c -> q a b -> Prepared m a c #

Alternative m => Alternative (Prepared m x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

empty :: Prepared m x a #

(<|>) :: Prepared m x a -> Prepared m x a -> Prepared m x a #

some :: Prepared m x a -> Prepared m x [a] #

many :: Prepared m x a -> Prepared m x [a] #

Applicative m => Applicative (Prepared m x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

pure :: a -> Prepared m x a #

(<*>) :: Prepared m x (a -> b) -> Prepared m x a -> Prepared m x b #

liftA2 :: (a -> b -> c) -> Prepared m x a -> Prepared m x b -> Prepared m x c #

(*>) :: Prepared m x a -> Prepared m x b -> Prepared m x b #

(<*) :: Prepared m x a -> Prepared m x b -> Prepared m x a #

Functor m => Functor (Prepared m x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

fmap :: (a -> b) -> Prepared m x a -> Prepared m x b #

(<$) :: a -> Prepared m x b -> Prepared m x a #

Generic (Prepared m x y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Associated Types

type Rep (Prepared m x y) :: Type -> Type #

Methods

from :: Prepared m x y -> Rep (Prepared m x y) x0 #

to :: Rep (Prepared m x y) x0 -> Prepared m x y #

type Rep1 (Prepared m x :: Type -> Type) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

type Rep1 (Prepared m x :: Type -> Type) = D1 ('MetaData "Prepared" "Squeal.PostgreSQL.Session.Statement" "squeal-postgresql-0.9.1.3-FfCgbPNg57H53ZAGizr3Nu" 'False) (C1 ('MetaCons "Prepared" 'PrefixI 'True) (S1 ('MetaSel ('Just "runPrepared") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ((FUN 'Many x :: TYPE LiftedRep -> Type) :.: Rec1 m) :*: S1 ('MetaSel ('Just "deallocate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (m ()))))
type Rep (Prepared m x y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

type Rep (Prepared m x y) = D1 ('MetaData "Prepared" "Squeal.PostgreSQL.Session.Statement" "squeal-postgresql-0.9.1.3-FfCgbPNg57H53ZAGizr3Nu" 'False) (C1 ('MetaCons "Prepared" 'PrefixI 'True) (S1 ('MetaSel ('Just "runPrepared") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (x -> m y)) :*: S1 ('MetaSel ('Just "deallocate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (m ()))))