squeal-postgresql-0.7.0.1: Squeal PostgreSQL Library

Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Session.Monad

Description

Run Statements in the mtl-style typeclass MonadPQ.

Synopsis

Documentation

>>> import Squeal.PostgreSQL

class Monad pq => MonadPQ db pq | pq -> db where Source #

MonadPQ is an mtl style constraint, similar to MonadState, for using LibPQ to run Statements.

Minimal complete definition

Nothing

Methods

executeParams Source #

Arguments

:: Statement db x y

query or manipulation

-> x

parameters

-> pq (Result y) 

executeParams runs a Statement which takes out-of-line parameters.

>>> import Data.Int (Int32, Int64)
>>> import Data.Monoid (Sum(Sum))
>>> :{
let
  sumOf :: Statement db (Int32, Int32) (Sum Int32)
  sumOf = query $ values_ $
    ( param @1 @('NotNull 'PGint4) +
      param @2 @('NotNull 'PGint4)
    ) `as` #getSum
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $ do
    result <- executeParams sumOf (2,2)
    firstRow result
:}
Just (Sum {getSum = 4})

executeParams Source #

Arguments

:: (MonadTrans t, MonadPQ db m, pq ~ t m) 
=> Statement db x y

query or manipulation

-> x

parameters

-> pq (Result y) 

executeParams runs a Statement which takes out-of-line parameters.

>>> import Data.Int (Int32, Int64)
>>> import Data.Monoid (Sum(Sum))
>>> :{
let
  sumOf :: Statement db (Int32, Int32) (Sum Int32)
  sumOf = query $ values_ $
    ( param @1 @('NotNull 'PGint4) +
      param @2 @('NotNull 'PGint4)
    ) `as` #getSum
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $ do
    result <- executeParams sumOf (2,2)
    firstRow result
:}
Just (Sum {getSum = 4})

executeParams_ Source #

Arguments

:: Statement db x ()

query or manipulation

-> x

parameters

-> pq () 

executeParams_ runs a returning-free Statement.

>>> type Column = 'NoDef :=> 'NotNull 'PGint4
>>> type Columns = '["col1" ::: Column, "col2" ::: Column]
>>> type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>> type DB = Public Schema
>>> import Data.Int(Int32)
>>> :{
let
  insertion :: Statement DB (Int32, Int32) ()
  insertion = manipulation $ insertInto_ #tab $ Values_ $
    Set (param @1 @('NotNull 'PGint4)) `as` #col1 :*
    Set (param @2 @('NotNull 'PGint4)) `as` #col2
  setup :: Definition (Public '[]) DB
  setup = createTable #tab
    ( notNullable int4 `as` #col1 :*
      notNullable int4 `as` #col2
    ) Nil
  teardown :: Definition DB (Public '[])
  teardown = dropTable #tab
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $
    define setup
    & pqThen (executeParams_ insertion (2,2))
    & pqThen (define teardown)
:}

execute Source #

Arguments

:: Statement db () y

query or manipulation

-> pq (Result y) 

execute runs a parameter-free Statement.

>>> import Data.Int(Int32)
>>> :{
let
  two :: Expr ('NotNull 'PGint4)
  two = 2
  twoPlusTwo :: Statement db () (Only Int32)
  twoPlusTwo = query $ values_ $ (two + two) `as` #fromOnly
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $ do
    result <- execute twoPlusTwo
    firstRow result
:}
Just (Only {fromOnly = 4})

execute_ :: Statement db () () -> pq () Source #

execute_ runs a parameter-free, returning-free Statement.

>>> :{
let
  silence :: Statement db () ()
  silence = manipulation $
    UnsafeManipulation "Set client_min_messages TO WARNING"
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $ execute_ silence
:}

executePrepared Source #

Arguments

:: Traversable list 
=> Statement db x y

query or manipulation

-> list x

list of parameters

-> pq (list (Result y)) 

executePrepared runs a Statement on a Traversable container by first preparing the statement, then running the prepared statement on each element.

>>> import Data.Int (Int32, Int64)
>>> import Data.Monoid (Sum(Sum))
>>> :{
let
  sumOf :: Statement db (Int32, Int32) (Sum Int32)
  sumOf = query $ values_ $
    ( param @1 @('NotNull 'PGint4) +
      param @2 @('NotNull 'PGint4)
    ) `as` #getSum
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $ do
    results <- executePrepared sumOf [(2,2),(3,3),(4,4)]
    traverse firstRow results
:}
[Just (Sum {getSum = 4}),Just (Sum {getSum = 6}),Just (Sum {getSum = 8})]

executePrepared Source #

Arguments

:: (MonadTrans t, MonadPQ db m, pq ~ t m) 
=> Traversable list 
=> Statement db x y

query or manipulation

-> list x

list of parameters

-> pq (list (Result y)) 

executePrepared runs a Statement on a Traversable container by first preparing the statement, then running the prepared statement on each element.

>>> import Data.Int (Int32, Int64)
>>> import Data.Monoid (Sum(Sum))
>>> :{
let
  sumOf :: Statement db (Int32, Int32) (Sum Int32)
  sumOf = query $ values_ $
    ( param @1 @('NotNull 'PGint4) +
      param @2 @('NotNull 'PGint4)
    ) `as` #getSum
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $ do
    results <- executePrepared sumOf [(2,2),(3,3),(4,4)]
    traverse firstRow results
:}
[Just (Sum {getSum = 4}),Just (Sum {getSum = 6}),Just (Sum {getSum = 8})]

executePrepared_ Source #

Arguments

:: Foldable list 
=> Statement db x ()

query or manipulation

-> list x

list of parameters

-> pq () 

executePrepared_ runs a returning-free Statement on a Foldable container by first preparing the statement, then running the prepared statement on each element.

>>> type Column = 'NoDef :=> 'NotNull 'PGint4
>>> type Columns = '["col1" ::: Column, "col2" ::: Column]
>>> type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>> type DB = Public Schema
>>> import Data.Int(Int32)
>>> :{
let
  insertion :: Statement DB (Int32, Int32) ()
  insertion = manipulation $ insertInto_ #tab $ Values_ $
    Set (param @1 @('NotNull 'PGint4)) `as` #col1 :*
    Set (param @2 @('NotNull 'PGint4)) `as` #col2
  setup :: Definition (Public '[]) DB
  setup = createTable #tab
    ( notNullable int4 `as` #col1 :*
      notNullable int4 `as` #col2
    ) Nil
  teardown :: Definition DB (Public '[])
  teardown = dropTable #tab
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $
    define setup
    & pqThen (executePrepared_ insertion [(2,2),(3,3),(4,4)])
    & pqThen (define teardown)
:}

executePrepared_ Source #

Arguments

:: (MonadTrans t, MonadPQ db m, pq ~ t m) 
=> Foldable list 
=> Statement db x ()

query or manipulation

-> list x

list of parameters

-> pq () 

executePrepared_ runs a returning-free Statement on a Foldable container by first preparing the statement, then running the prepared statement on each element.

>>> type Column = 'NoDef :=> 'NotNull 'PGint4
>>> type Columns = '["col1" ::: Column, "col2" ::: Column]
>>> type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>> type DB = Public Schema
>>> import Data.Int(Int32)
>>> :{
let
  insertion :: Statement DB (Int32, Int32) ()
  insertion = manipulation $ insertInto_ #tab $ Values_ $
    Set (param @1 @('NotNull 'PGint4)) `as` #col1 :*
    Set (param @2 @('NotNull 'PGint4)) `as` #col2
  setup :: Definition (Public '[]) DB
  setup = createTable #tab
    ( notNullable int4 `as` #col1 :*
      notNullable int4 `as` #col2
    ) Nil
  teardown :: Definition DB (Public '[])
  teardown = dropTable #tab
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $
    define setup
    & pqThen (executePrepared_ insertion [(2,2),(3,3),(4,4)])
    & pqThen (define teardown)
:}
Instances
MonadPQ db m => MonadPQ db (MaybeT m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Monad

Methods

executeParams :: Statement db x y -> x -> MaybeT m (Result y) Source #

executeParams_ :: Statement db x () -> x -> MaybeT m () Source #

execute :: Statement db () y -> MaybeT m (Result y) Source #

execute_ :: Statement db () () -> MaybeT m () Source #

executePrepared :: Traversable list => Statement db x y -> list x -> MaybeT m (list (Result y)) Source #

executePrepared_ :: Foldable list => Statement db x () -> list x -> MaybeT m () Source #

MonadPQ db m => MonadPQ db (ExceptT e m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Monad

Methods

executeParams :: Statement db x y -> x -> ExceptT e m (Result y) Source #

executeParams_ :: Statement db x () -> x -> ExceptT e m () Source #

execute :: Statement db () y -> ExceptT e m (Result y) Source #

execute_ :: Statement db () () -> ExceptT e m () Source #

executePrepared :: Traversable list => Statement db x y -> list x -> ExceptT e m (list (Result y)) Source #

executePrepared_ :: Foldable list => Statement db x () -> list x -> ExceptT e m () Source #

(Monoid w, MonadPQ db m) => MonadPQ db (WriterT w m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Monad

Methods

executeParams :: Statement db x y -> x -> WriterT w m (Result y) Source #

executeParams_ :: Statement db x () -> x -> WriterT w m () Source #

execute :: Statement db () y -> WriterT w m (Result y) Source #

execute_ :: Statement db () () -> WriterT w m () Source #

executePrepared :: Traversable list => Statement db x y -> list x -> WriterT w m (list (Result y)) Source #

executePrepared_ :: Foldable list => Statement db x () -> list x -> WriterT w m () Source #

(Monoid w, MonadPQ db m) => MonadPQ db (WriterT w m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Monad

Methods

executeParams :: Statement db x y -> x -> WriterT w m (Result y) Source #

executeParams_ :: Statement db x () -> x -> WriterT w m () Source #

execute :: Statement db () y -> WriterT w m (Result y) Source #

execute_ :: Statement db () () -> WriterT w m () Source #

executePrepared :: Traversable list => Statement db x y -> list x -> WriterT w m (list (Result y)) Source #

executePrepared_ :: Foldable list => Statement db x () -> list x -> WriterT w m () Source #

MonadPQ db m => MonadPQ db (StateT s m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Monad

Methods

executeParams :: Statement db x y -> x -> StateT s m (Result y) Source #

executeParams_ :: Statement db x () -> x -> StateT s m () Source #

execute :: Statement db () y -> StateT s m (Result y) Source #

execute_ :: Statement db () () -> StateT s m () Source #

executePrepared :: Traversable list => Statement db x y -> list x -> StateT s m (list (Result y)) Source #

executePrepared_ :: Foldable list => Statement db x () -> list x -> StateT s m () Source #

MonadPQ db m => MonadPQ db (StateT s m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Monad

Methods

executeParams :: Statement db x y -> x -> StateT s m (Result y) Source #

executeParams_ :: Statement db x () -> x -> StateT s m () Source #

execute :: Statement db () y -> StateT s m (Result y) Source #

execute_ :: Statement db () () -> StateT s m () Source #

executePrepared :: Traversable list => Statement db x y -> list x -> StateT s m (list (Result y)) Source #

executePrepared_ :: Foldable list => Statement db x () -> list x -> StateT s m () Source #

MonadPQ db m => MonadPQ db (ReaderT r m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Monad

Methods

executeParams :: Statement db x y -> x -> ReaderT r m (Result y) Source #

executeParams_ :: Statement db x () -> x -> ReaderT r m () Source #

execute :: Statement db () y -> ReaderT r m (Result y) Source #

execute_ :: Statement db () () -> ReaderT r m () Source #

executePrepared :: Traversable list => Statement db x y -> list x -> ReaderT r m (list (Result y)) Source #

executePrepared_ :: Foldable list => Statement db x () -> list x -> ReaderT r m () Source #

MonadPQ db m => MonadPQ db (IdentityT m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Monad

Methods

executeParams :: Statement db x y -> x -> IdentityT m (Result y) Source #

executeParams_ :: Statement db x () -> x -> IdentityT m () Source #

execute :: Statement db () y -> IdentityT m (Result y) Source #

execute_ :: Statement db () () -> IdentityT m () Source #

executePrepared :: Traversable list => Statement db x y -> list x -> IdentityT m (list (Result y)) Source #

executePrepared_ :: Foldable list => Statement db x () -> list x -> IdentityT m () Source #

MonadPQ db m => MonadPQ db (ContT r m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Monad

Methods

executeParams :: Statement db x y -> x -> ContT r m (Result y) Source #

executeParams_ :: Statement db x () -> x -> ContT r m () Source #

execute :: Statement db () y -> ContT r m (Result y) Source #

execute_ :: Statement db () () -> ContT r m () Source #

executePrepared :: Traversable list => Statement db x y -> list x -> ContT r m (list (Result y)) Source #

executePrepared_ :: Foldable list => Statement db x () -> list x -> ContT r m () Source #

(MonadIO io, db0 ~ db, db1 ~ db) => MonadPQ db (PQ db0 db1 io) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session

Methods

executeParams :: Statement db x y -> x -> PQ db0 db1 io (Result y) Source #

executeParams_ :: Statement db x () -> x -> PQ db0 db1 io () Source #

execute :: Statement db () y -> PQ db0 db1 io (Result y) Source #

execute_ :: Statement db () () -> PQ db0 db1 io () Source #

executePrepared :: Traversable list => Statement db x y -> list x -> PQ db0 db1 io (list (Result y)) Source #

executePrepared_ :: Foldable list => Statement db x () -> list x -> PQ db0 db1 io () Source #

(Monoid w, MonadPQ db m) => MonadPQ db (RWST r w s m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Monad

Methods

executeParams :: Statement db x y -> x -> RWST r w s m (Result y) Source #

executeParams_ :: Statement db x () -> x -> RWST r w s m () Source #

execute :: Statement db () y -> RWST r w s m (Result y) Source #

execute_ :: Statement db () () -> RWST r w s m () Source #

executePrepared :: Traversable list => Statement db x y -> list x -> RWST r w s m (list (Result y)) Source #

executePrepared_ :: Foldable list => Statement db x () -> list x -> RWST r w s m () Source #

(Monoid w, MonadPQ db m) => MonadPQ db (RWST r w s m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Monad

Methods

executeParams :: Statement db x y -> x -> RWST r w s m (Result y) Source #

executeParams_ :: Statement db x () -> x -> RWST r w s m () Source #

execute :: Statement db () y -> RWST r w s m (Result y) Source #

execute_ :: Statement db () () -> RWST r w s m () Source #

executePrepared :: Traversable list => Statement db x y -> list x -> RWST r w s m (list (Result y)) Source #

executePrepared_ :: Foldable list => Statement db x () -> list x -> RWST r w s m () Source #

manipulateParams Source #

Arguments

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

insertInto, update, or deleteFrom, and friends

-> x 
-> pq (Result y) 

manipulateParams runs a Manipulation.

>>> type Column = 'NoDef :=> 'NotNull 'PGint4
>>> type Columns = '["col1" ::: Column, "col2" ::: Column]
>>> type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>> type DB = Public Schema
>>> import Control.Monad.IO.Class
>>> import Data.Int(Int32)
>>> :{
let
  insertAdd :: Manipulation_ DB (Int32, Int32) (Only Int32)
  insertAdd = insertInto #tab 
    ( Values_ $
        Set (param @1 @('NotNull 'PGint4)) `as` #col1 :*
        Set (param @2 @('NotNull 'PGint4)) `as` #col2
    ) OnConflictDoRaise
    ( Returning_ ((#col1 + #col2) `as` #fromOnly) )
  setup :: Definition (Public '[]) DB
  setup = createTable #tab
    ( notNullable int4 `as` #col1 :*
      notNullable int4 `as` #col2
    ) Nil
  teardown :: Definition DB (Public '[])
  teardown = dropTable #tab
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $
    define setup
    & pqThen
      ( do
          result <- manipulateParams insertAdd (2::Int32,2::Int32)
          Just (Only answer) <- firstRow result
          liftIO $ print (answer :: Int32)
      )
    & pqThen (define teardown)
:}
4

manipulateParams_ Source #

Arguments

:: (MonadPQ db pq, GenericParams db params x xs) 
=> Manipulation '[] db params '[]

insertInto_, update_, or deleteFrom_, and friends

-> x 
-> pq () 

manipulateParams_ runs a Manipulation, for a returning-free statement.

>>> type Column = 'NoDef :=> 'NotNull 'PGint4
>>> type Columns = '["col1" ::: Column, "col2" ::: Column]
>>> type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>> type DB = Public Schema
>>> import Data.Int(Int32)
>>> :{
let
  insertion :: Manipulation_ DB (Int32, Int32) ()
  insertion = insertInto_ #tab $ Values_ $
    Set (param @1 @('NotNull 'PGint4)) `as` #col1 :*
    Set (param @2 @('NotNull 'PGint4)) `as` #col2
  setup :: Definition (Public '[]) DB
  setup = createTable #tab
    ( notNullable int4 `as` #col1 :*
      notNullable int4 `as` #col2
    ) Nil
  teardown :: Definition DB (Public '[])
  teardown = dropTable #tab
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $
    define setup
    & pqThen (manipulateParams_ insertion (2::Int32,2::Int32))
    & pqThen (define teardown)
:}

manipulate :: (MonadPQ db pq, GenericRow row y ys) => Manipulation '[] db '[] row -> pq (Result y) Source #

manipulate runs a Manipulation, for a parameter-free statement.

>>> type Column = 'NoDef :=> 'NotNull 'PGint4
>>> type Columns = '["col1" ::: Column, "col2" ::: Column]
>>> type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>> type DB = Public Schema
>>> import Control.Monad.IO.Class
>>> import Data.Int(Int32)
>>> :{
let
  insertTwoPlusTwo :: Manipulation_ DB () (Only Int32)
  insertTwoPlusTwo = insertInto #tab 
    (Values_ $ Set 2 `as` #col1 :* Set 2 `as` #col2)
    OnConflictDoRaise
    (Returning_ ((#col1 + #col2) `as` #fromOnly))
  setup :: Definition (Public '[]) DB
  setup = createTable #tab
    ( notNullable int4 `as` #col1 :*
      notNullable int4 `as` #col2
    ) Nil
  teardown :: Definition DB (Public '[])
  teardown = dropTable #tab
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $
    define setup
    & pqThen
      ( do
          result <- manipulate insertTwoPlusTwo
          Just (Only answer) <- firstRow result
          liftIO $ print (answer :: Int32)
      )
    & pqThen (define teardown)
:}
4

manipulate_ :: MonadPQ db pq => Manipulation '[] db '[] '[] -> pq () Source #

manipulate_ runs a Manipulation, for a returning-free, parameter-free statement.

>>> :{
let
  silence :: Manipulation_ db () ()
  silence = UnsafeManipulation "Set client_min_messages TO WARNING"
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $ manipulate_ silence
:}

runQueryParams Source #

Arguments

:: (MonadPQ db pq, GenericParams db params x xs, IsRecord y ys, AllZip FromField row ys) 
=> Query '[] '[] db params row

select and friends

-> x 
-> pq (Result y) 

runQueryParams runs a Query.

>>> import Data.Int (Int32, Int64)
>>> import Control.Monad.IO.Class
>>> import Data.Monoid (Sum(Sum))
>>> :{
let
  sumOf :: Query_ db (Int32, Int32) (Sum Int32)
  sumOf = values_ $
    ( param @1 @('NotNull 'PGint4) +
      param @2 @('NotNull 'PGint4)
    ) `as` #getSum
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $ do
    result <- runQueryParams sumOf (2::Int32,2::Int32)
    Just (Sum four) <- firstRow result
    liftIO $ print (four :: Int32)
:}
4

runQuery Source #

Arguments

:: (MonadPQ db pq, IsRecord y ys, AllZip FromField row ys) 
=> Query '[] '[] db '[] row

select and friends

-> pq (Result y) 

runQuery runs a Query, for a parameter-free statement.

>>> import Data.Int (Int32, Int64)
>>> import Control.Monad.IO.Class
>>> import Data.Monoid (Sum(Sum))
>>> :{
let
  twoPlusTwo :: Query_ db () (Sum Int32)
  twoPlusTwo = values_ $ (2 + 2) `as` #getSum
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $ do
    result <- runQuery twoPlusTwo
    Just (Sum four) <- firstRow result
    liftIO $ print (four :: Int32)
:}
4

traversePrepared Source #

Arguments

:: (MonadPQ db pq, GenericParams db params x xs, Traversable list, IsRecord y ys, AllZip FromField row ys) 
=> Manipulation '[] db params row

insertInto, update, or deleteFrom, and friends

-> list x 
-> pq (list (Result y)) 

traversePrepared runs a Manipulation on a Traversable container by first preparing the statement, then running the prepared statement on each element.

>>> type Column = 'NoDef :=> 'NotNull 'PGint4
>>> type Columns = '["col1" ::: Column, "col2" ::: Column]
>>> type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>> type DB = Public Schema
>>> import Control.Monad.IO.Class
>>> import Data.Int(Int32)
>>> :{
let
  insertAdd :: Manipulation_ DB (Int32, Int32) (Only Int32)
  insertAdd = insertInto #tab 
    ( Values_ $
        Set (param @1 @('NotNull 'PGint4)) `as` #col1 :*
        Set (param @2 @('NotNull 'PGint4)) `as` #col2
    ) OnConflictDoRaise
    ( Returning_ ((#col1 + #col2) `as` #fromOnly) )
  setup :: Definition (Public '[]) DB
  setup = createTable #tab
    ( notNullable int4 `as` #col1 :*
      notNullable int4 `as` #col2
    ) Nil
  teardown :: Definition DB (Public '[])
  teardown = dropTable #tab
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $
    define setup
    & pqThen
      ( do
          results <- traversePrepared insertAdd [(2::Int32,2::Int32),(3,3),(4,4)]
          answers <- traverse firstRow results
          liftIO $ print [answer :: Int32 | Just (Only answer) <- answers]
      )
    & pqThen (define teardown)
:}
[4,6,8]

forPrepared Source #

Arguments

:: (MonadPQ db pq, GenericParams db params x xs, Traversable list, IsRecord y ys, AllZip FromField row ys) 
=> list x 
-> Manipulation '[] db params row

insertInto, update, or deleteFrom, and friends

-> pq (list (Result y)) 

forPrepared is a flipped traversePrepared

>>> type Column = 'NoDef :=> 'NotNull 'PGint4
>>> type Columns = '["col1" ::: Column, "col2" ::: Column]
>>> type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>> type DB = Public Schema
>>> import Control.Monad.IO.Class
>>> import Data.Int(Int32)
>>> :{
let
  insertAdd :: Manipulation_ DB (Int32, Int32) (Only Int32)
  insertAdd = insertInto #tab 
    ( Values_ $
        Set (param @1 @('NotNull 'PGint4)) `as` #col1 :*
        Set (param @2 @('NotNull 'PGint4)) `as` #col2
    ) OnConflictDoRaise
    ( Returning_ ((#col1 + #col2) `as` #fromOnly) )
  setup :: Definition (Public '[]) DB
  setup = createTable #tab
    ( notNullable int4 `as` #col1 :*
      notNullable int4 `as` #col2
    ) Nil
  teardown :: Definition DB (Public '[])
  teardown = dropTable #tab
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $
    define setup
    & pqThen
      ( do
          results <- forPrepared [(2::Int32,2::Int32),(3,3),(4,4)] insertAdd
          answers <- traverse firstRow results
          liftIO $ print [answer :: Int32 | Just (Only answer) <- answers]
      )
    & pqThen (define teardown)
:}
[4,6,8]

traversePrepared_ Source #

Arguments

:: (MonadPQ db pq, GenericParams db params x xs, Foldable list) 
=> Manipulation '[] db params '[]

insertInto_, update_, or deleteFrom_, and friends

-> list x 
-> pq () 

traversePrepared_ runs a returning-free Manipulation on a Foldable container by first preparing the statement, then running the prepared statement on each element.

>>> type Column = 'NoDef :=> 'NotNull 'PGint4
>>> type Columns = '["col1" ::: Column, "col2" ::: Column]
>>> type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>> type DB = Public Schema
>>> import Data.Int(Int32)
>>> :{
let
  insertion :: Manipulation_ DB (Int32, Int32) ()
  insertion = insertInto_ #tab $ Values_ $
    Set (param @1 @('NotNull 'PGint4)) `as` #col1 :*
    Set (param @2 @('NotNull 'PGint4)) `as` #col2
  setup :: Definition (Public '[]) DB
  setup = createTable #tab
    ( notNullable int4 `as` #col1 :*
      notNullable int4 `as` #col2
    ) Nil
  teardown :: Definition DB (Public '[])
  teardown = dropTable #tab
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $
    define setup
    & pqThen (traversePrepared_ insertion [(2::Int32,2::Int32),(3,3),(4,4)])
    & pqThen (define teardown)
:}

forPrepared_ Source #

Arguments

:: (MonadPQ db pq, GenericParams db params x xs, Foldable list) 
=> list x 
-> Manipulation '[] db params '[]

insertInto_, update_, or deleteFrom_, and friends

-> pq () 

forPrepared_ is a flipped traversePrepared_

>>> type Column = 'NoDef :=> 'NotNull 'PGint4
>>> type Columns = '["col1" ::: Column, "col2" ::: Column]
>>> type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>> type DB = Public Schema
>>> import Data.Int(Int32)
>>> :{
let
  insertion :: Manipulation_ DB (Int32, Int32) ()
  insertion = insertInto_ #tab $ Values_ $
    Set (param @1 @('NotNull 'PGint4)) `as` #col1 :*
    Set (param @2 @('NotNull 'PGint4)) `as` #col2
  setup :: Definition (Public '[]) DB
  setup = createTable #tab
    ( notNullable int4 `as` #col1 :*
      notNullable int4 `as` #col2
    ) Nil
  teardown :: Definition DB (Public '[])
  teardown = dropTable #tab
in
  withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $
    define setup
    & pqThen (forPrepared_ [(2::Int32,2::Int32),(3,3),(4,4)] insertion)
    & pqThen (define teardown)
:}