postgresql-query-1.4.0: Sql interpolating quasiquote plus some kind of primitive ORM using it

Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.Query.Functions

Contents

Synopsis

Raw query execution

pgQuery :: (HasPostgres m, MonadLogger m, ToSqlBuilder q, FromRow r) => q -> m [r] Source

Execute query generated by SqlBuilder. Typical use case:

let userName = "Vovka Erohin" :: Text
pgQuery [sqlExp| SELECT id, name FROM users WHERE name = #{userName}|]

Or

let userName = "Vovka Erohin" :: Text
pgQuery $ Qp "SELECT id, name FROM users WHERE name = ?" [userName]

Which is almost the same. In both cases proper value escaping is performed so you stay protected from sql injections.

pgExecute :: (HasPostgres m, MonadLogger m, ToSqlBuilder q) => q -> m Int64 Source

Execute arbitrary query and return count of affected rows

pgQueryEntities :: (ToSqlBuilder q, HasPostgres m, MonadLogger m, Entity a, FromRow a, FromField (EntityId a)) => q -> m [Ent a] Source

Executes arbitrary query and parses it as entities and their ids

Transactions

pgWithTransaction :: (HasPostgres m, MonadBaseControl IO m, TransactionSafe m) => m a -> m a Source

Execute all queries inside one transaction. Rollback transaction on exceptions

pgWithSavepoint :: (HasPostgres m, MonadBaseControl IO m, TransactionSafe m) => m a -> m a Source

Same as pgWithTransaction but executes queries inside savepoint

pgWithTransactionMode :: (HasPostgres m, MonadBaseControl IO m, TransactionSafe m) => TransactionMode -> m a -> m a Source

Wrapper for withTransactionMode: Execute an action inside a SQL transaction with a given transaction mode.

pgWithTransactionModeRetry :: (HasPostgres m, MonadBaseControl IO m, TransactionSafe m) => TransactionMode -> (SqlError -> Bool) -> m a -> m a Source

Wrapper for withTransactionModeRetry: Like pgWithTransactionMode, but also takes a custom callback to determine if a transaction should be retried if an SqlError occurs. If the callback returns True, then the transaction will be retried. If the callback returns False, or an exception other than an SqlError occurs then the transaction will be rolled back and the exception rethrown.

pgWithTransactionSerializable :: (HasPostgres m, MonadBaseControl IO m, TransactionSafe m) => m a -> m a Source

Wrapper for withTransactionSerializable: Execute an action inside of a Serializable transaction. If a serialization failure occurs, roll back the transaction and try again. Be warned that this may execute the IO action multiple times.

A Serializable transaction creates the illusion that your program has exclusive access to the database. This means that, even in a concurrent setting, you can perform queries in sequence without having to worry about what might happen between one statement and the next.

Work with entities

pgInsertEntity :: forall a m. (HasPostgres m, MonadLogger m, Entity a, ToRow a, FromField (EntityId a)) => a -> m (EntityId a) Source

Insert new entity and return it's id

pgInsertManyEntities :: forall a m. (Entity a, HasPostgres m, MonadLogger m, ToRow a) => [a] -> m Int64 Source

Insert many entities without returning list of id like pgInsertManyEntitiesId does

pgInsertManyEntitiesId :: forall a m. (Entity a, HasPostgres m, MonadLogger m, ToRow a, FromField (EntityId a)) => [a] -> m [EntityId a] Source

Same as pgInsertEntity but insert many entities at one action. Returns list of id's of inserted entities

pgSelectEntities Source

Arguments

:: (Functor m, HasPostgres m, MonadLogger m, Entity a, FromRow a, ToSqlBuilder q, FromField (EntityId a)) 
=> (FN -> FN)

Entity fields name modifier, e.g. ("tablename"<>). Each field of entity will be processed by this modifier before pasting to the query

-> q

part of query just after SELECT .. FROM table.

-> m [Ent a] 

Select entities as pairs of (id, entity).

handler :: Handler [Ent a]
handler = do
    now <- liftIO getCurrentTime
    let back = addUTCTime (days  (-7)) now
    pgSelectEntities id
        [sqlExp|WHERE created BETWEEN #{now} AND #{back}
               ORDER BY created|]

handler2 :: Text -> Handler [Ent Foo]
handler2 fvalue = do
    pgSelectEntities ("t"<>)
        [sqlExp|AS t INNER JOIN table2 AS t2
                ON t.t2_id = t2.id
                WHERE t.field = #{fvalue}
                ORDER BY t2.field2|]
   -- Here the query will be: SELECT ... FROM tbl AS t INNER JOIN ...

pgSelectJustEntities :: forall m a q. (Functor m, HasPostgres m, MonadLogger m, Entity a, FromRow a, ToSqlBuilder q) => (FN -> FN) -> q -> m [a] Source

Same as pgSelectEntities but do not select id

pgSelectEntitiesBy :: forall a m b. (Functor m, HasPostgres m, MonadLogger m, Entity a, ToMarkedRow b, FromRow a, FromField (EntityId a)) => b -> m [Ent a] Source

Select entities by condition formed from MarkedRow. Usefull function when you know

pgGetEntity :: forall m a. (ToField (EntityId a), Entity a, HasPostgres m, MonadLogger m, FromRow a, Functor m) => EntityId a -> m (Maybe a) Source

Select entity by id

getUser :: EntityId User ->  Handler User
getUser uid = do
    pgGetEntity uid
        >>= maybe notFound return

pgGetEntityBy Source

Arguments

:: (Entity a, HasPostgres m, MonadLogger m, ToMarkedRow b, FromField (EntityId a), FromRow a, Functor m) 
=> b

uniq constrained list of fields and values

-> m (Maybe (Ent a)) 

Get entity by some fields constraint

getUser :: UserName -> Handler User
getUser name = do
    pgGetEntityBy
        (MR [("name", mkValue name),
             ("active", mkValue True)])
        >>= maybe notFound return

The query here will be like

pgQuery [sqlExp|SELECT id, name, phone ... FROM users WHERE name = {True}|]

pgDeleteEntity :: forall a m. (Entity a, HasPostgres m, MonadLogger m, ToField (EntityId a), Functor m) => EntityId a -> m Bool Source

Delete entity.

rmUser :: EntityId User -> Handler ()
rmUser uid = do
    pgDeleteEntity uid

Return True if row was actually deleted.

pgUpdateEntity :: forall a b m. (ToMarkedRow b, Entity a, HasPostgres m, MonadLogger m, ToField (EntityId a), Functor m, Typeable a, Typeable b) => EntityId a -> b -> m Bool Source

Update entity using ToMarkedRow instanced value. Requires Proxy while EntityId is not a data type.

fixUser :: Text -> EntityId User -> Handler ()
fixUser username uid = do
    pgGetEntity uid
        >>= maybe notFound run
  where
    run user =
        pgUpdateEntity uid
        $ MR [("active", mkValue True)
              ("name", mkValue username)]

Returns True if record was actually updated and False if there was not row with such id (or was more than 1, in fact)

pgSelectCount :: forall m a q. (Entity a, HasPostgres m, MonadLogger m, ToSqlBuilder q) => Proxy a -> q -> m Integer Source

Select count of entities with given query

activeUsers :: Handler Integer
activeUsers = do
    pgSelectCount (Proxy :: Proxy User)
        [sqlExp|WHERE active = #{True}|]

Auxiliary functions

pgRepsertRow Source

Arguments

:: (HasPostgres m, MonadLogger m, ToMarkedRow wrow, ToMarkedRow urow) 
=> Text

Table name

-> wrow

where condition

-> urow

update row

-> m () 

Perform repsert of the same row, first trying "update where" then "insert" with concatenated fields. Which means that if you run

pgRepsertRow "emails" (MR [("user_id", mkValue uid)]) (MR [("email", mkValue email)])

Then firstly will be performed

UPDATE "emails" SET email = 'foo@bar.com' WHERE "user_id" = 1234

And if no one row is affected (which is returned by pgExecute), then

INSERT INTO "emails" ("user_id", "email") VALUES (1234, 'foo@bar.com')

will be performed