Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class Monad pq => MonadPQ db pq | pq -> db where
- executeParams :: Statement db x y -> x -> pq (Result y)
- executeParams_ :: Statement db x () -> x -> pq ()
- execute :: Statement db () y -> pq (Result y)
- execute_ :: Statement db () () -> pq ()
- prepare :: Statement db x y -> pq (Prepared pq x (Result y))
- prepare_ :: Statement db x () -> pq (Prepared pq x ())
- manipulateParams :: (MonadPQ db pq, GenericParams db params x xs, GenericRow row y ys) => Manipulation '[] db params row -> x -> pq (Result y)
- manipulateParams_ :: (MonadPQ db pq, GenericParams db params x xs) => Manipulation '[] db params '[] -> x -> pq ()
- manipulate :: (MonadPQ db pq, GenericRow row y ys) => Manipulation '[] db '[] row -> pq (Result y)
- manipulate_ :: MonadPQ db pq => Manipulation '[] db '[] '[] -> pq ()
- runQueryParams :: (MonadPQ db pq, GenericParams db params x xs, GenericRow row y ys) => Query '[] '[] db params row -> x -> pq (Result y)
- runQuery :: (MonadPQ db pq, GenericRow row y ys) => Query '[] '[] db '[] row -> pq (Result y)
- executePrepared :: (MonadPQ db pq, Traversable list) => Statement db x y -> list x -> pq (list (Result y))
- executePrepared_ :: (MonadPQ db pq, Foldable list) => Statement db x () -> list x -> pq ()
- traversePrepared :: (MonadPQ db pq, GenericParams db params x xs, GenericRow row y ys, Traversable list) => Manipulation '[] db params row -> list x -> pq (list (Result y))
- forPrepared :: (MonadPQ db pq, GenericParams db params x xs, GenericRow row y ys, Traversable list) => list x -> Manipulation '[] db params row -> pq (list (Result y))
- traversePrepared_ :: (MonadPQ db pq, GenericParams db params x xs, Foldable list) => Manipulation '[] db params '[] -> list x -> pq ()
- forPrepared_ :: (MonadPQ db pq, GenericParams db params x xs, Foldable list) => list x -> Manipulation '[] db params '[] -> pq ()
- preparedFor :: MonadPQ db pq => (Prepared pq a (Result b) -> Prepared pq s t) -> Statement db a b -> s -> pq t
MonadPQ
class Monad pq => MonadPQ db pq | pq -> db where Source #
MonadPQ
is an mtl
style constraint, similar to
MonadState
, for using LibPQ
to run Statement
s.
Nothing
executeParams
runs a Statement
which takes out-of-line
parameter
s.
>>>
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})
default executeParams :: (MonadTrans t, MonadPQ db m, pq ~ t m) => Statement db x y -> x -> pq (Result y) Source #
:: 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
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})
:: Statement db () () | query or manipulation |
-> pq () |
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 :}
prepare
creates a Prepared
statement. When prepare
is executed,
the specified Statement
is parsed, analyzed, and rewritten.
>>>
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 prepared <- prepare sumOf result <- runPrepared prepared (2,2) deallocate prepared firstRow result :} Just (Sum {getSum = 4})
default prepare :: (MonadTrans t, MonadPQ db m, pq ~ t m) => Statement db x y -> pq (Prepared pq x (Result y)) Source #
prepare_
creates a Prepared
statement. When prepare_
is executed,
the specified Statement
is parsed, analyzed, and rewritten.
>>>
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 session :: PQ DB DB IO () session = do prepared <- prepare_ insertion runPrepared prepared (2,2) deallocate prepared teardown :: Definition DB (Public '[]) teardown = dropTable #tab in withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $ define setup & pqThen session & pqThen (define teardown) :}
Instances
Manipulate
:: (MonadPQ db pq, GenericParams db params x xs, GenericRow row y ys) | |
=> Manipulation '[] db params row |
|
-> 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
:: (MonadPQ db pq, GenericParams db params x xs) | |
=> Manipulation '[] db params '[] |
|
-> 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 :}
Run Query
:: (MonadPQ db pq, GenericParams db params x xs, GenericRow row y ys) | |
=> Query '[] '[] db params row |
|
-> 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
:: (MonadPQ db pq, GenericRow row y ys) | |
=> Query '[] '[] db '[] row |
|
-> 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
Prepared
:: (MonadPQ db pq, 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})]
:: (MonadPQ db pq, 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) :}
:: (MonadPQ db pq, GenericParams db params x xs, GenericRow row y ys, Traversable list) | |
=> Manipulation '[] db params row |
|
-> 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]
:: (MonadPQ db pq, GenericParams db params x xs, GenericRow row y ys, Traversable list) | |
=> list x | |
-> Manipulation '[] db params row |
|
-> 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]
:: (MonadPQ db pq, GenericParams db params x xs, Foldable list) | |
=> Manipulation '[] db params '[] |
|
-> 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) :}
:: (MonadPQ db pq, GenericParams db params x xs, Foldable list) | |
=> list x | |
-> Manipulation '[] db params '[] |
|
-> 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) :}