snaplet-postgresql-simple-0.3.0.3: postgresql-simple snaplet for the Snap Framework

Safe HaskellNone

Snap.Snaplet.PostgresqlSimple

Contents

Description

This snaplet makes it simple to use a PostgreSQL database from your Snap application and is based on the excellent postgresql-simple library (http://hackage.haskell.org/package/postgresql-simple) by Leon Smith (adapted from Bryan O'Sullivan's mysql-simple). Now, adding a database to your web app takes just two simple steps.

First, include this snaplet in your application's state.

 data App = App
     { ... -- Other state needed in your app
     , _db :: Snaplet Postgres
     }

Next, call the pgsInit from your application's initializer.

 appInit = makeSnaplet ... $ do
     ...
     d <- nestSnaplet "db" db pgsInit
     return $ App ... d

Now you can use any of the postgresql-simple wrapper functions defined in this module anywhere in your application handlers. For instance:

 postHandler :: Handler App App ()
 postHandler = do
     posts <- with db $ query_ "select * from blog_post"
     ...

Optionally, if you find yourself doing many database queries, you can eliminate some of the boilerplate by defining a HasPostgres instance for your application.

 instance HasPostgres (Handler b App) where
   getPostgresState = with db get

With this code, our postHandler example no longer requires the with function:

 postHandler :: Handler App App ()
 postHandler = do
     posts <- query_ "select * from blog_post"
     ...

The first time you run an application with the postgresql-simple snaplet, a configuration file devel.cfg is created in the snaplets/postgresql-simple directory underneath your project root. It specifies how to connect to your PostgreSQL server and what user, password, and database to use. Edit this file and modify the values appropriately and you'll be off and running.

If you want to have out-of-the-box authentication, look at the documentation for the Snap.Snaplet.Auth.Backends.PostgresqlSimple module.

Synopsis

The Snaplet

data Postgres Source

The state for the postgresql-simple snaplet. To use it in your app include this in your application state and use pgsInit to initialize it.

Constructors

Postgres 

Fields

pgPool :: Pool Connection

Function for retrieving the connection pool

Instances

MonadCatchIO m => HasPostgres (ReaderT (Snaplet Postgres) m)

A convenience instance to make it easier to use this snaplet in the Initializer monad like this:

 d <- nestSnaplet "db" db pgsInit
 count <- liftIO $ runReaderT (execute "INSERT ..." params) d
MonadCatchIO m => HasPostgres (ReaderT Postgres m)

A convenience instance to make it easier to use functions written for this snaplet in non-snaplet contexts.

HasPostgres (Handler b Postgres)

Default instance

class MonadCatchIO m => HasPostgres m whereSource

Instantiate this typeclass on 'Handler b YourAppState' so this snaplet can find the connection source. If you need to have multiple instances of the postgres snaplet in your application, then don't provide this instance and leverage the default instance by using "with dbLens" in front of calls to snaplet-postgresql-simple functions.

Instances

MonadCatchIO m => HasPostgres (ReaderT (Snaplet Postgres) m)

A convenience instance to make it easier to use this snaplet in the Initializer monad like this:

 d <- nestSnaplet "db" db pgsInit
 count <- liftIO $ runReaderT (execute "INSERT ..." params) d
MonadCatchIO m => HasPostgres (ReaderT Postgres m)

A convenience instance to make it easier to use functions written for this snaplet in non-snaplet contexts.

HasPostgres (Handler b Postgres)

Default instance

pgsInit :: SnapletInit b PostgresSource

Initialize the snaplet

Wrappers and re-exports

query :: (HasPostgres m, ToRow q, FromRow r) => Query -> q -> m [r]Source

See query

query_ :: (HasPostgres m, FromRow r) => Query -> m [r]Source

See query_

fold :: (HasPostgres m, FromRow row, ToRow params, MonadCatchIO m) => Query -> params -> b -> (b -> row -> IO b) -> m bSource

foldWithOptions :: (HasPostgres m, FromRow row, ToRow params, MonadCatchIO m) => FoldOptions -> Query -> params -> b -> (b -> row -> IO b) -> m bSource

fold_ :: (HasPostgres m, FromRow row, MonadCatchIO m) => Query -> b -> (b -> row -> IO b) -> m bSource

foldWithOptions_ :: (HasPostgres m, FromRow row, MonadCatchIO m) => FoldOptions -> Query -> b -> (b -> row -> IO b) -> m bSource

forEach :: (HasPostgres m, FromRow r, ToRow q, MonadCatchIO m) => Query -> q -> (r -> IO ()) -> m ()Source

forEach_ :: (HasPostgres m, FromRow r, MonadCatchIO m) => Query -> (r -> IO ()) -> m ()Source

returning :: (HasPostgres m, ToRow q, FromRow r) => Query -> [q] -> m [r]Source

data Query

A query string. This type is intended to make it difficult to construct a SQL query by concatenating string fragments, as that is an extremely common way to accidentally introduce SQL injection vulnerabilities into an application.

This type is an instance of IsString, so the easiest way to construct a query is to enable the OverloadedStrings language extension and then simply write the query in double quotes.

 {-# LANGUAGE OverloadedStrings #-}

 import Database.PostgreSQL.Simple

 q :: Query
 q = "select ?"

The underlying type is a ByteString, and literal Haskell strings that contain Unicode characters will be correctly transformed to UTF-8.

newtype In a

Wrap a list of values for use in an IN clause. Replaces a single "?" character with a parenthesized list of rendered values.

Example:

 query c "select * from whatever where id in ?" (Only (In [3,4,5]))

Constructors

In a 

Instances

Functor In 
Typeable1 In 
Eq a => Eq (In a) 
Ord a => Ord (In a) 
Read a => Read (In a) 
Show a => Show (In a) 
ToField a => ToField (In [a]) 

newtype Binary a

Wrap binary data for use as a bytea value.

Constructors

Binary a 

newtype Only a

A single-value "collection".

This is useful if you need to supply a single parameter to a SQL query, or extract a single column from a SQL result.

Parameter example:

query c "select x from scores where x > ?" (Only (42::Int))

Result example:

xs <- query_ c "select id from users"
forM_ xs $ \(Only id) -> {- ... -}

Constructors

Only 

Fields

fromOnly :: a
 

Instances

Functor Only 
Typeable1 Only 
Eq a => Eq (Only a) 
Ord a => Ord (Only a) 
Read a => Read (Only a) 
Show a => Show (Only a) 
FromField a => FromRow (Only a) 
ToField a => ToRow (Only a) 

data FormatError

Exception thrown if a Query could not be formatted correctly. This may occur if the number of '?' characters in the query string does not match the number of parameters provided.

data QueryError

Exception thrown if query is used to perform an INSERT-like operation, or execute is used to perform a SELECT-like operation.

data ResultError

Exception thrown if conversion from a SQL value to a Haskell value fails.

data IsolationLevel

Of the four isolation levels defined by the SQL standard, these are the three levels distinguished by PostgreSQL as of version 9.0. See http://www.postgresql.org/docs/9.1/static/transaction-iso.html for more information. Note that prior to PostgreSQL 9.0, RepeatableRead was equivalent to Serializable.

Constructors

DefaultIsolationLevel

the isolation level will be taken from PostgreSQL's per-connection default_transaction_isolation variable, which is initialized according to the server's config. The default configuration is ReadCommitted.

ReadCommitted 
RepeatableRead 
Serializable 

data ReadWriteMode

Constructors

DefaultReadWriteMode

the read-write mode will be taken from PostgreSQL's per-connection default_transaction_read_only variable, which is initialized according to the server's config. The default configuration is ReadWrite.

ReadWrite 
ReadOnly 

data h :. t

A composite type to parse your custom data structures without having to define dummy newtype wrappers every time.

 instance FromRow MyData where ...
 instance FromRow MyData2 where ...

then I can do the following for free:

 res <- query' c ...
 forM res $ \(MyData{..} :. MyData2{..}) -> do
   ....

Constructors

h :. t 

Instances

Typeable2 :. 
(Eq h, Eq t) => Eq (:. h t) 
(Ord h, Ord t) => Ord (:. h t) 
(Read h, Read t) => Read (:. h t) 
(Show h, Show t) => Show (:. h t) 
(FromRow a, FromRow b) => FromRow (:. a b) 
(ToRow a, ToRow b) => ToRow (:. a b) 

class ToRow a where

A collection type that can be turned into a list of rendering Actions.

Instances should use the render method of the Param class to perform conversion of each element of the collection.

Methods

toRow :: a -> [Action]

ToField a collection of values.

Instances

ToRow () 
ToField a => ToRow [a] 
ToField a => ToRow (Only a) 
(ToField a, ToField b) => ToRow (a, b) 
(ToRow a, ToRow b) => ToRow (:. a b) 
(ToField a, ToField b, ToField c) => ToRow (a, b, c) 
(ToField a, ToField b, ToField c, ToField d) => ToRow (a, b, c, d) 
(ToField a, ToField b, ToField c, ToField d, ToField e) => ToRow (a, b, c, d, e) 
(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f) => ToRow (a, b, c, d, e, f) 
(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g) => ToRow (a, b, c, d, e, f, g) 
(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h) => ToRow (a, b, c, d, e, f, g, h) 
(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i) => ToRow (a, b, c, d, e, f, g, h, i) 
(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j) => ToRow (a, b, c, d, e, f, g, h, i, j) 

class FromRow a where

A collection type that can be converted from a sequence of fields. Instances are provided for tuples up to 10 elements and lists of any length.

Note that instances can defined outside of postgresql-simple, which is often useful. For example, here's an instance for a user-defined pair:

data User = User { name :: String, fileQuota :: Int }

instance FromRow User where
     fromRow = User <$> field <*> field

The number of calls to field must match the number of fields returned in a single row of the query result. Otherwise, a ConversionFailed exception will be thrown.

Note that field evaluates it's result to WHNF, so the caveats listed in previous versions of postgresql-simple no longer apply. Instead, look at the caveats associated with user-defined implementations of fromRow.

Methods

fromRow :: RowParser a

Instances

FromRow AuthUser 
FromField a => FromRow [a] 
FromField a => FromRow (Only a) 
(FromField a, FromField b) => FromRow (a, b) 
(FromRow a, FromRow b) => FromRow (:. a b) 
(FromField a, FromField b, FromField c) => FromRow (a, b, c) 
(FromField a, FromField b, FromField c, FromField d) => FromRow (a, b, c, d) 
(FromField a, FromField b, FromField c, FromField d, FromField e) => FromRow (a, b, c, d, e) 
(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f) => FromRow (a, b, c, d, e, f) 
(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g) => FromRow (a, b, c, d, e, f, g) 
(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h) => FromRow (a, b, c, d, e, f, g, h) 
(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i) => FromRow (a, b, c, d, e, f, g, h, i) 
(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j) => FromRow (a, b, c, d, e, f, g, h, i, j) 

defaultConnectInfo :: ConnectInfo

Default information for setting up a connection.

Defaults are as follows:

  • Server on localhost
  • Port on 5432
  • User postgres
  • No password
  • Database postgres

Use as in the following example:

 connect defaultConnectInfo { connectHost = "db.example.com" }