module Database.PostgreSQL.Query.Functions
(
pgQuery
, pgQueryWithMasker
, pgExecute
, pgExecuteWithMasker
, pgWithTransaction
, pgWithSavepoint
, pgWithTransactionMode
, pgWithTransactionModeRetry
, pgWithTransactionSerializable
, pgRepsertRow
) where
import Data.Int ( Int64 )
import Database.PostgreSQL.Query.Import
import Database.PostgreSQL.Query.Internal
import Database.PostgreSQL.Query.SqlBuilder
import Database.PostgreSQL.Query.TH
import Database.PostgreSQL.Query.Types
import Database.PostgreSQL.Simple
import Database.PostgreSQL.Simple.Transaction
import qualified Data.Text.Encoding as T
pgQuery
:: (HasPostgres m, MonadLogger m, ToSqlBuilder q, FromRow r)
=> q
-> m [r]
pgQuery = pgQueryWithMasker defaultLogMasker
pgExecute
:: (HasPostgres m, MonadLogger m, ToSqlBuilder q)
=> q
-> m Int64
pgExecute = pgExecuteWithMasker defaultLogMasker
pgQueryWithMasker
:: (HasPostgres m, MonadLogger m, ToSqlBuilder q, FromRow r)
=> LogMasker
-> q
-> m [r]
pgQueryWithMasker masker q = withPGConnection $ \c -> do
(queryBs, logBs) <- liftBase $ runSqlBuilder c masker $ toSqlBuilder q
logDebugN $ T.decodeUtf8 logBs
liftBase $ query_ c queryBs
pgExecuteWithMasker
:: (HasPostgres m, MonadLogger m, ToSqlBuilder q)
=> LogMasker
-> q
-> m Int64
pgExecuteWithMasker masker q = withPGConnection $ \c -> do
(queryBs, logBs) <- liftBase $ runSqlBuilder c masker $ toSqlBuilder q
logDebugN $ T.decodeUtf8 logBs
liftBase $ execute_ c queryBs
pgWithTransaction :: (HasPostgres m, MonadBaseControl IO m, TransactionSafe m)
=> m a
-> m a
pgWithTransaction action = withPGConnection $ \con -> do
control $ \runInIO -> do
withTransaction con $ runInIO action
pgWithSavepoint :: (HasPostgres m, MonadBaseControl IO m, TransactionSafe m) => m a -> m a
pgWithSavepoint action = withPGConnection $ \con -> do
control $ \runInIO -> do
withSavepoint con $ runInIO action
pgWithTransactionMode :: (HasPostgres m, MonadBaseControl IO m, TransactionSafe m)
=> TransactionMode
-> m a
-> m a
pgWithTransactionMode tmode ma = withPGConnection $ \con -> do
control $ \runInIO -> do
withTransactionMode tmode con $ runInIO ma
pgWithTransactionModeRetry :: (HasPostgres m, MonadBaseControl IO m, TransactionSafe m)
=> TransactionMode
-> (SqlError -> Bool)
-> m a
-> m a
pgWithTransactionModeRetry tmode epred ma = withPGConnection $ \con -> do
control $ \runInIO -> do
withTransactionModeRetry tmode epred con $ runInIO ma
pgWithTransactionSerializable :: (HasPostgres m, MonadBaseControl IO m, TransactionSafe m)
=> m a
-> m a
pgWithTransactionSerializable ma = withPGConnection $ \con -> do
control $ \runInIO -> do
withTransactionSerializable con $ runInIO ma
pgRepsertRow
:: ( MonadPostgres m, MonadLogger m
, ToMarkedRow wrow, ToMarkedRow urow)
=> FN
-> wrow
-> urow
-> m ()
pgRepsertRow tname wrow urow = do
let wmr = toMarkedRow wrow
aff <- pgExecute $ updateTable tname urow
[sqlExp|WHERE ^{mrToBuilder "AND" wmr}|]
when (aff == 0) $ do
let umr = toMarkedRow urow
imr = wmr <> umr
_ <- pgExecute $ insertInto tname imr
return ()