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

Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.Query.Entity.Functions

Contents

Synopsis

Work with entities

pgInsertEntity :: forall a m. (MonadPostgres 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, MonadPostgres 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, MonadPostgres 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, MonadPostgres 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, MonadPostgres 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, MonadPostgres 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, FromRow a, MonadPostgres m, MonadLogger m, 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, MonadPostgres 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}|]

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

Select count of entities with given query

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

Executes arbitrary query and parses it as entities and their ids

pgDeleteEntity :: forall a m. (Entity a, MonadPostgres 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, MonadPostgres 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, MonadPostgres m, MonadLogger m, ToSqlBuilder q) => Proxy a -> q -> m Integer Source #