{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Opaleye.Manipulation (module Opaleye.Manipulation,
HSql.OnConflict(..)) where
import qualified Opaleye.Field as F
import qualified Opaleye.RunSelect as RS
import qualified Opaleye.Internal.RunQuery as IRQ
import qualified Opaleye.Table as T
import qualified Opaleye.Internal.Table as TI
import Opaleye.Internal.Column (Column)
import Opaleye.Internal.Helpers ((.:), (.:.))
import Opaleye.Internal.Inferrable (Inferrable, runInferrable)
import Opaleye.Internal.Manipulation (Updater(Updater))
import qualified Opaleye.Internal.Manipulation as MI
import Opaleye.SqlTypes (SqlBool)
import qualified Opaleye.Internal.HaskellDB.Sql as HSql
import qualified Database.PostgreSQL.Simple as PGS
import qualified Data.Profunctor.Product.Default as D
import Data.Int (Int64)
import Data.String (fromString)
import qualified Data.List.NonEmpty as NEL
runInsert_ :: PGS.Connection
-> Insert haskells
-> IO haskells
runInsert_ :: Connection -> Insert haskells -> IO haskells
runInsert_ Connection
conn Insert haskells
i = case Insert haskells
i of
Insert Table fieldsW fieldsR
table_ [fieldsW]
rows_ Returning fieldsR haskells
returning_ Maybe OnConflict
onConflict_ ->
let insert :: Connection -> Table fieldsW fieldsR -> [fieldsW] -> IO haskells
insert = case (Returning fieldsR haskells
returning_, Maybe OnConflict
onConflict_) of
(Returning fieldsR haskells
MI.Count, Maybe OnConflict
Nothing) ->
Connection -> Table fieldsW fieldsR -> [fieldsW] -> IO haskells
forall columns columns'.
Connection -> Table columns columns' -> [columns] -> IO Int64
runInsertMany
(Returning fieldsR haskells
MI.Count, Just OnConflict
HSql.DoNothing) ->
Connection -> Table fieldsW fieldsR -> [fieldsW] -> IO haskells
forall columns columns'.
Connection -> Table columns columns' -> [columns] -> IO Int64
runInsertManyOnConflictDoNothing
(MI.ReturningExplicit FromFields b c
qr fieldsR -> b
f, Maybe OnConflict
oc) ->
\Connection
c Table fieldsW fieldsR
t [fieldsW]
r -> FromFields b c
-> Connection
-> Table fieldsW fieldsR
-> [fieldsW]
-> (fieldsR -> b)
-> Maybe OnConflict
-> IO [c]
forall columnsReturned haskells columnsW columnsR.
FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> Maybe OnConflict
-> IO [haskells]
MI.runInsertManyReturningExplicit FromFields b c
qr Connection
c Table fieldsW fieldsR
t [fieldsW]
r fieldsR -> b
f Maybe OnConflict
oc
in Connection -> Table fieldsW fieldsR -> [fieldsW] -> IO haskells
insert Connection
conn Table fieldsW fieldsR
table_ [fieldsW]
rows_
runUpdate_ :: PGS.Connection
-> Update haskells
-> IO haskells
runUpdate_ :: Connection -> Update haskells -> IO haskells
runUpdate_ Connection
conn Update haskells
i = case Update haskells
i of
Update Table fieldsW fieldsR
table_ fieldsR -> fieldsW
updateWith_ fieldsR -> Field SqlBool
where_ Returning fieldsR haskells
returning_ ->
let update :: Connection
-> Table fieldsW fieldsR
-> (fieldsR -> fieldsW)
-> (fieldsR -> Column SqlBool)
-> IO haskells
update = case Returning fieldsR haskells
returning_ of
Returning fieldsR haskells
MI.Count ->
Connection
-> Table fieldsW fieldsR
-> (fieldsR -> fieldsW)
-> (fieldsR -> Column SqlBool)
-> IO haskells
forall columnsW columnsR.
Connection
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> IO Int64
runUpdate
MI.ReturningExplicit FromFields b c
qr fieldsR -> b
f ->
\Connection
c Table fieldsW fieldsR
t fieldsR -> fieldsW
u fieldsR -> Column SqlBool
w -> FromFields b c
-> Connection
-> Table fieldsW fieldsR
-> (fieldsR -> fieldsW)
-> (fieldsR -> Column SqlBool)
-> (fieldsR -> b)
-> IO [c]
forall columnsReturned haskells columnsW columnsR.
FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> (columnsR -> columnsReturned)
-> IO [haskells]
runUpdateReturningExplicit FromFields b c
qr Connection
c Table fieldsW fieldsR
t fieldsR -> fieldsW
u fieldsR -> Column SqlBool
w fieldsR -> b
f
in Connection
-> Table fieldsW fieldsR
-> (fieldsR -> fieldsW)
-> (fieldsR -> Column SqlBool)
-> IO haskells
update Connection
conn Table fieldsW fieldsR
table_ fieldsR -> fieldsW
updateWith_ fieldsR -> Column SqlBool
fieldsR -> Field SqlBool
where_
runDelete_ :: PGS.Connection
-> Delete haskells
-> IO haskells
runDelete_ :: Connection -> Delete haskells -> IO haskells
runDelete_ Connection
conn Delete haskells
i = case Delete haskells
i of
Delete Table fieldsW fieldsR
table_ fieldsR -> Field SqlBool
where_ Returning fieldsR haskells
returning_ ->
let delete :: Connection
-> Table fieldsW fieldsR
-> (fieldsR -> Column SqlBool)
-> IO haskells
delete = case Returning fieldsR haskells
returning_ of
Returning fieldsR haskells
MI.Count ->
Connection
-> Table fieldsW fieldsR
-> (fieldsR -> Column SqlBool)
-> IO haskells
forall a columnsR.
Connection
-> Table a columnsR -> (columnsR -> Column SqlBool) -> IO Int64
runDelete
MI.ReturningExplicit FromFields b c
qr fieldsR -> b
f ->
\Connection
c Table fieldsW fieldsR
t fieldsR -> Column SqlBool
w -> FromFields b c
-> Connection
-> Table fieldsW fieldsR
-> (fieldsR -> Column SqlBool)
-> (fieldsR -> b)
-> IO [c]
forall columnsReturned haskells a columnsR.
FromFields columnsReturned haskells
-> Connection
-> Table a columnsR
-> (columnsR -> Column SqlBool)
-> (columnsR -> columnsReturned)
-> IO [haskells]
MI.runDeleteReturningExplicit FromFields b c
qr Connection
c Table fieldsW fieldsR
t fieldsR -> Column SqlBool
w fieldsR -> b
f
in Connection
-> Table fieldsW fieldsR
-> (fieldsR -> Column SqlBool)
-> IO haskells
delete Connection
conn Table fieldsW fieldsR
table_ fieldsR -> Column SqlBool
fieldsR -> Field SqlBool
where_
data Insert haskells = forall fieldsW fieldsR. Insert
{ ()
iTable :: T.Table fieldsW fieldsR
, ()
iRows :: [fieldsW]
, ()
iReturning :: MI.Returning fieldsR haskells
, Insert haskells -> Maybe OnConflict
iOnConflict :: Maybe HSql.OnConflict
}
data Update haskells = forall fieldsW fieldsR. Update
{ ()
uTable :: T.Table fieldsW fieldsR
, ()
uUpdateWith :: fieldsR -> fieldsW
, ()
uWhere :: fieldsR -> F.Field SqlBool
, ()
uReturning :: MI.Returning fieldsR haskells
}
updateEasy :: D.Default Updater fieldsR fieldsW
=> (fieldsR -> fieldsR)
-> (fieldsR -> fieldsW)
updateEasy :: (fieldsR -> fieldsR) -> fieldsR -> fieldsW
updateEasy fieldsR -> fieldsR
u = fieldsR -> fieldsW
u' (fieldsR -> fieldsW) -> (fieldsR -> fieldsR) -> fieldsR -> fieldsW
forall b c a. (b -> c) -> (a -> b) -> a -> c
. fieldsR -> fieldsR
u
where Updater fieldsR -> fieldsW
u' = Updater fieldsR fieldsW
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def
data Delete haskells = forall fieldsW fieldsR. Delete
{ ()
dTable :: T.Table fieldsW fieldsR
, ()
dWhere :: fieldsR -> F.Field SqlBool
, ()
dReturning :: MI.Returning fieldsR haskells
}
rCount :: MI.Returning fieldsR Int64
rCount :: Returning fieldsR Int64
rCount = Returning fieldsR Int64
forall a. Returning a Int64
MI.Count
rReturning :: D.Default RS.FromFields fields haskells
=> (fieldsR -> fields)
-> MI.Returning fieldsR [haskells]
rReturning :: (fieldsR -> fields) -> Returning fieldsR [haskells]
rReturning = FromFields fields haskells
-> (fieldsR -> fields) -> Returning fieldsR [haskells]
forall fields haskells fieldsR.
FromFields fields haskells
-> (fieldsR -> fields) -> Returning fieldsR [haskells]
rReturningExplicit FromFields fields haskells
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def
rReturningI :: D.Default (Inferrable RS.FromFields) fields haskells
=> (fieldsR -> fields)
-> MI.Returning fieldsR [haskells]
rReturningI :: (fieldsR -> fields) -> Returning fieldsR [haskells]
rReturningI = FromFields fields haskells
-> (fieldsR -> fields) -> Returning fieldsR [haskells]
forall fields haskells fieldsR.
FromFields fields haskells
-> (fieldsR -> fields) -> Returning fieldsR [haskells]
rReturningExplicit (Inferrable FromFields fields haskells -> FromFields fields haskells
forall (p :: * -> * -> *) a b. Inferrable p a b -> p a b
runInferrable Inferrable FromFields fields haskells
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def)
rReturningExplicit :: RS.FromFields fields haskells
-> (fieldsR -> fields)
-> MI.Returning fieldsR [haskells]
rReturningExplicit :: FromFields fields haskells
-> (fieldsR -> fields) -> Returning fieldsR [haskells]
rReturningExplicit = FromFields fields haskells
-> (fieldsR -> fields) -> Returning fieldsR [haskells]
forall fields haskells fieldsR.
FromFields fields haskells
-> (fieldsR -> fields) -> Returning fieldsR [haskells]
MI.ReturningExplicit
{-# DEPRECATED runInsertManyOnConflictDoNothing "Use 'runInsert_'. Will be removed in version 0.8." #-}
runInsertManyOnConflictDoNothing :: PGS.Connection
-> T.Table columns columns'
-> [columns]
-> IO Int64
runInsertManyOnConflictDoNothing :: Connection -> Table columns columns' -> [columns] -> IO Int64
runInsertManyOnConflictDoNothing Connection
conn Table columns columns'
table_ [columns]
columns =
case [columns] -> Maybe (NonEmpty columns)
forall a. [a] -> Maybe (NonEmpty a)
NEL.nonEmpty [columns]
columns of
Maybe (NonEmpty columns)
Nothing -> Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
0
Just NonEmpty columns
columns' -> (Connection -> Query -> IO Int64
PGS.execute_ Connection
conn (Query -> IO Int64) -> (String -> Query) -> String -> IO Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Query
forall a. IsString a => String -> a
fromString (String -> IO Int64)
-> (Table columns columns'
-> NonEmpty columns -> Maybe OnConflict -> String)
-> Table columns columns'
-> NonEmpty columns
-> Maybe OnConflict
-> IO Int64
forall r z a b c.
(r -> z) -> (a -> b -> c -> r) -> a -> b -> c -> z
.:. Table columns columns'
-> NonEmpty columns -> Maybe OnConflict -> String
forall columnsW columnsR.
Table columnsW columnsR
-> NonEmpty columnsW -> Maybe OnConflict -> String
MI.arrangeInsertManySql)
Table columns columns'
table_ NonEmpty columns
columns' (OnConflict -> Maybe OnConflict
forall a. a -> Maybe a
Just OnConflict
HSql.DoNothing)
{-# DEPRECATED runInsertManyReturningOnConflictDoNothing "Use 'runInsert_'. Will be removed in version 0.8." #-}
runInsertManyReturningOnConflictDoNothing
:: (D.Default RS.FromFields columnsReturned haskells)
=> PGS.Connection
-> T.Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> IO [haskells]
runInsertManyReturningOnConflictDoNothing :: Connection
-> Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> IO [haskells]
runInsertManyReturningOnConflictDoNothing =
FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> IO [haskells]
forall columnsReturned haskells columnsW columnsR.
FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> IO [haskells]
runInsertManyReturningOnConflictDoNothingExplicit FromFields columnsReturned haskells
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def
{-# DEPRECATED runInsertMany "Use 'runInsert_' instead. Will be removed in version 0.8." #-}
runInsertMany :: PGS.Connection
-> T.Table columns columns'
-> [columns]
-> IO Int64
runInsertMany :: Connection -> Table columns columns' -> [columns] -> IO Int64
runInsertMany Connection
conn Table columns columns'
t [columns]
columns = case [columns] -> Maybe (NonEmpty columns)
forall a. [a] -> Maybe (NonEmpty a)
NEL.nonEmpty [columns]
columns of
Maybe (NonEmpty columns)
Nothing -> Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
0
Just NonEmpty columns
columns' -> (Connection -> Query -> IO Int64
PGS.execute_ Connection
conn (Query -> IO Int64) -> (String -> Query) -> String -> IO Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Query
forall a. IsString a => String -> a
fromString (String -> IO Int64)
-> (Table columns columns' -> NonEmpty columns -> String)
-> Table columns columns'
-> NonEmpty columns
-> IO Int64
forall r z a b. (r -> z) -> (a -> b -> r) -> a -> b -> z
.: Table columns columns' -> NonEmpty columns -> String
forall columns a. Table columns a -> NonEmpty columns -> String
MI.arrangeInsertManySqlI) Table columns columns'
t NonEmpty columns
columns'
{-# DEPRECATED runInsertManyReturning "Use 'runInsert_' instead. Will be removed in version 0.8." #-}
runInsertManyReturning :: (D.Default RS.FromFields columnsReturned haskells)
=> PGS.Connection
-> T.Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> IO [haskells]
runInsertManyReturning :: Connection
-> Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> IO [haskells]
runInsertManyReturning = FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> IO [haskells]
forall columnsReturned haskells columnsW columnsR.
FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> IO [haskells]
runInsertManyReturningExplicit FromFields columnsReturned haskells
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def
{-# DEPRECATED runInsertReturningExplicit "Use 'runInsert_' instead. Will be removed in version 0.8." #-}
runInsertReturningExplicit :: RS.FromFields columnsReturned haskells
-> PGS.Connection
-> T.Table columnsW columnsR
-> columnsW
-> (columnsR -> columnsReturned)
-> IO [haskells]
runInsertReturningExplicit :: FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> columnsW
-> (columnsR -> columnsReturned)
-> IO [haskells]
runInsertReturningExplicit = FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> columnsW
-> (columnsR -> columnsReturned)
-> IO [haskells]
forall columnsReturned haskells columnsW columnsR.
FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> columnsW
-> (columnsR -> columnsReturned)
-> IO [haskells]
MI.runInsertReturningExplicit
{-# DEPRECATED runInsertManyReturningExplicit "Use 'runInsert_' instead. Will be removed in version 0.8." #-}
runInsertManyReturningExplicit :: RS.FromFields columnsReturned haskells
-> PGS.Connection
-> T.Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> IO [haskells]
runInsertManyReturningExplicit :: FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> IO [haskells]
runInsertManyReturningExplicit = FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> IO [haskells]
forall columnsReturned haskells columnsW columnsR.
FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> IO [haskells]
MI.runInsertManyReturningExplicitI
{-# DEPRECATED runInsertManyReturningOnConflictDoNothingExplicit "Use 'runInsert_' instead. Will be removed in version 0.8." #-}
runInsertManyReturningOnConflictDoNothingExplicit
:: RS.FromFields columnsReturned haskells
-> PGS.Connection
-> T.Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> IO [haskells]
runInsertManyReturningOnConflictDoNothingExplicit :: FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> IO [haskells]
runInsertManyReturningOnConflictDoNothingExplicit FromFields columnsReturned haskells
qr Connection
conn Table columnsW columnsR
t [columnsW]
columns columnsR -> columnsReturned
f =
FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> Maybe OnConflict
-> IO [haskells]
forall columnsReturned haskells columnsW columnsR.
FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> Maybe OnConflict
-> IO [haskells]
MI.runInsertManyReturningExplicit FromFields columnsReturned haskells
qr Connection
conn Table columnsW columnsR
t [columnsW]
columns columnsR -> columnsReturned
f (OnConflict -> Maybe OnConflict
forall a. a -> Maybe a
Just OnConflict
HSql.DoNothing)
{-# DEPRECATED runUpdateEasy "Use 'runUpdate_' instead. Will be removed in version 0.8." #-}
runUpdateEasy :: D.Default Updater columnsR columnsW
=> PGS.Connection
-> T.Table columnsW columnsR
-> (columnsR -> columnsR)
-> (columnsR -> Column SqlBool)
-> IO Int64
runUpdateEasy :: Connection
-> Table columnsW columnsR
-> (columnsR -> columnsR)
-> (columnsR -> Column SqlBool)
-> IO Int64
runUpdateEasy Connection
conn Table columnsW columnsR
table_ columnsR -> columnsR
u = Connection
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> IO Int64
forall columnsW columnsR.
Connection
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> IO Int64
runUpdate Connection
conn Table columnsW columnsR
table_ (columnsR -> columnsW
u' (columnsR -> columnsW)
-> (columnsR -> columnsR) -> columnsR -> columnsW
forall b c a. (b -> c) -> (a -> b) -> a -> c
. columnsR -> columnsR
u)
where Updater columnsR -> columnsW
u' = Updater columnsR columnsW
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def
{-# DEPRECATED runUpdate "Use 'runUpdate_' instead. Will be removed in version 0.8." #-}
runUpdate :: PGS.Connection
-> T.Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> IO Int64
runUpdate :: Connection
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> IO Int64
runUpdate Connection
conn = Connection -> Query -> IO Int64
PGS.execute_ Connection
conn (Query -> IO Int64) -> (String -> Query) -> String -> IO Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Query
forall a. IsString a => String -> a
fromString (String -> IO Int64)
-> (Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> String)
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> IO Int64
forall r z a b c.
(r -> z) -> (a -> b -> c -> r) -> a -> b -> c -> z
.:. Table columnsW columnsR
-> (columnsR -> columnsW) -> (columnsR -> Column SqlBool) -> String
forall columnsW columnsR.
Table columnsW columnsR
-> (columnsR -> columnsW) -> (columnsR -> Column SqlBool) -> String
MI.arrangeUpdateSql
{-# DEPRECATED runUpdateReturning "Use 'runUpdate_' instead. Will be removed in version 0.8." #-}
runUpdateReturning :: (D.Default RS.FromFields columnsReturned haskells)
=> PGS.Connection
-> T.Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> (columnsR -> columnsReturned)
-> IO [haskells]
runUpdateReturning :: Connection
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> (columnsR -> columnsReturned)
-> IO [haskells]
runUpdateReturning = FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> (columnsR -> columnsReturned)
-> IO [haskells]
forall columnsReturned haskells columnsW columnsR.
FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> (columnsR -> columnsReturned)
-> IO [haskells]
runUpdateReturningExplicit FromFields columnsReturned haskells
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def
{-# DEPRECATED runUpdateReturningExplicit "Use 'runUpdate_' instead. Will be removed in version 0.8." #-}
runUpdateReturningExplicit :: RS.FromFields columnsReturned haskells
-> PGS.Connection
-> T.Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> (columnsR -> columnsReturned)
-> IO [haskells]
runUpdateReturningExplicit :: FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> (columnsR -> columnsReturned)
-> IO [haskells]
runUpdateReturningExplicit FromFields columnsReturned haskells
qr Connection
conn Table columnsW columnsR
t columnsR -> columnsW
update columnsR -> Column SqlBool
cond columnsR -> columnsReturned
r =
RowParser haskells -> Connection -> Query -> IO [haskells]
forall r. RowParser r -> Connection -> Query -> IO [r]
PGS.queryWith_ RowParser haskells
parser Connection
conn
(String -> Query
forall a. IsString a => String -> a
fromString (Unpackspec columnsReturned ()
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> (columnsR -> columnsReturned)
-> String
forall columnsReturned ignored columnsW columnsR.
Unpackspec columnsReturned ignored
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> (columnsR -> columnsReturned)
-> String
MI.arrangeUpdateReturningSql Unpackspec columnsReturned ()
u Table columnsW columnsR
t columnsR -> columnsW
update columnsR -> Column SqlBool
cond columnsR -> columnsReturned
r))
where IRQ.QueryRunner Unpackspec columnsReturned ()
u columnsReturned -> RowParser haskells
_ columnsReturned -> Int
_ = FromFields columnsReturned haskells
qr
parser :: RowParser haskells
parser = FromFields columnsReturned haskells
-> columnsReturned -> RowParser haskells
forall columns haskells.
FromFields columns haskells -> columns -> RowParser haskells
IRQ.prepareRowParser FromFields columnsReturned haskells
qr (columnsR -> columnsReturned
r columnsR
v)
TI.View columnsR
v = TableFields columnsW columnsR -> View columnsR
forall writeColumns viewColumns.
TableFields writeColumns viewColumns -> View viewColumns
TI.tableColumnsView (Table columnsW columnsR -> TableFields columnsW columnsR
forall writeColumns viewColumns.
Table writeColumns viewColumns
-> TableFields writeColumns viewColumns
TI.tableColumns Table columnsW columnsR
t)
{-# DEPRECATED runDelete "Use 'runDelete_' instead. Will be removed in version 0.8." #-}
runDelete :: PGS.Connection
-> T.Table a columnsR
-> (columnsR -> Column SqlBool)
-> IO Int64
runDelete :: Connection
-> Table a columnsR -> (columnsR -> Column SqlBool) -> IO Int64
runDelete Connection
conn = Connection -> Query -> IO Int64
PGS.execute_ Connection
conn (Query -> IO Int64) -> (String -> Query) -> String -> IO Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Query
forall a. IsString a => String -> a
fromString (String -> IO Int64)
-> (Table a columnsR -> (columnsR -> Column SqlBool) -> String)
-> Table a columnsR
-> (columnsR -> Column SqlBool)
-> IO Int64
forall r z a b. (r -> z) -> (a -> b -> r) -> a -> b -> z
.: Table a columnsR -> (columnsR -> Column SqlBool) -> String
forall a columnsR.
Table a columnsR -> (columnsR -> Column SqlBool) -> String
MI.arrangeDeleteSql