Hi guys! Here is yet another some-level library to work with PostgreSQL DB. 

http://hackage.haskell.org/package/postgresql-query

This library uses `postgresql-query` and is a list of helpers/workarounds to generate 
complex queries more safely and parse result.

What it contains: 

1. interplating quasiquote `sqlExp` which uses instances of `ToField` typeclass to paste 
   values inside query. 
   It looks like this:

   let val = "'hello'" :: Text
       q = [sqlExp|SELECT field1 FROM tbl WHERE field2 = #{val}|]
   
   where `val` is an arbitrary Haskell expression which type has instance of `ToField` 
   Resulting query will be like: 

   "SELECT field1 FROM tbl WHERE field2 = '''hello'''"

   Yes, proper string escaping is performed authomatically like using this '?'-like 
   queries with parameters. 

   Resulting type of quasiquote is `SqlBuilder` which uses bytestring builders inside and 
   can be concatenated efficiently.

   There is also posibility to paste one query inside another like: 

   let q2 = [sqlExp|SELECT field1 f FROM (^{q}) WHERE field1 is not null|]

   so `q2` will generate nested query.

   sqlExp also removes SQL comments and removes long sequences of space characters. It also 
   properly handles string literals and quoted identifiers inside quasiquotes.

2. Typeclass `HasPostgres`, simple connection reader `PgMonadT` and functions like
   `pgQuery` to perform queries. 
   http://hackage.haskell.org/package/postgresql-query-1.0.1/docs/Database-PostgreSQL-Query-Functions.html

3. TH functions to authomatically derive `FromRow` and `ToRow` instances
   (from postgresql-simple)
   http://hackage.haskell.org/package/postgresql-query-1.0.1/docs/Database-PostgreSQL-Query-TH.html

4. Some kind of primitive pre-ORM which generates queries for CRUD-ing simple record types. 
   It looks like:

    data User = User
      { userName              :: !Text
      , userPasswordEncrypted :: !Text
      } deriving (Show, Eq, Ord, Typeable)

    type UserId = EntityId User

    $(deriveFromRow ''User)
    $(deriveToRow ''User)

    instance Entity User where
        newtype EntityId User
            = UserId { unUserId :: UUID } -- Note that you can use any type for id
            deriving (Show, Read, Ord, Eq,
                      FromField, ToField, PathPiece) -- To use with Yesod
        tableName _ = "users"
        fieldNames _ = [ "name"
                       , "password_encrypted" ]
                       
    runPgMonadT con $ do 
      uid <- pgInsertEntity $ User "name" "j27dna74ja784ha7"
      pgUpdateEntity uid $ MR [("name", mkValue "John")]
      pgDeleteEntity uid


There is also package http://hackage.haskell.org/package/postgresql-config which contains trivial code 
to make your postgresql-simple connection pool easily configurable.