snaplet-mysql-simple-0.2.0.3: mysql-simple snaplet for the Snap Framework

Safe HaskellNone
LanguageHaskell98

Snap.Snaplet.MysqlSimple

Contents

Description

This snaplet makes it simple to use a MariaDB or MySQL database from your Snap application and is a literal translation of snaplet-postgresql-simple by Doug Beardsley (https://github.com/mightybyte/snaplet-postgresql-simple). It uses the excellent mysql-simple library (http://hackage.haskell.org/package/mysql-simple) by Bryan O'Sullivan. 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 Mysql
    }

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

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

Now you can use any of the mysql-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 HasMysql instance for your application.

instance HasMysql (Handler b App) where
  getMysqlState = 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 mysql-simple snaplet, a configuration file devel.cfg is created in the snaplets/mysql-simple directory underneath your project root. It specifies how to connect to your MySQL or MariaDB 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.MysqlSimple module.

Synopsis

The Snaplet

data Mysql Source

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

Constructors

Mysql 

Fields

mysqlPool :: Pool Connection

Function for retrieving the connection pool

Instances

MonadCatchIO m => HasMysql (ReaderT (Snaplet Mysql) 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 => HasMysql (ReaderT Mysql m)

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

HasMysql (Handler b Mysql)

Default instance

class MonadCatchIO m => HasMysql m where Source

Instantiate this typeclass on 'Handler b YourAppState' so this snaplet can find the connection source. If you need to have multiple instances of the mysql 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-mysql-simple functions.

Instances

MonadCatchIO m => HasMysql (ReaderT (Snaplet Mysql) 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 => HasMysql (ReaderT Mysql m)

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

HasMysql (Handler b Mysql)

Default instance

mysqlInit :: SnapletInit b Mysql Source

Initialize the snaplet

mysqlInit' :: Config -> SnapletInit b Mysql Source

Initialize the snaplet

getConnectionInfo :: MonadIO m => Config -> m ConnectInfo Source

Produce a connection info from a config

Wrappers and re-exports

query :: (HasMysql m, QueryParams q, QueryResults r) => Query -> q -> m [r] Source

See query

query_ :: (HasMysql m, QueryResults r) => Query -> m [r] Source

See query_

fold :: (HasMysql m, QueryResults row, QueryParams params, MonadCatchIO m) => Query -> params -> b -> (b -> row -> IO b) -> m b Source

fold_ :: (HasMysql m, QueryResults row, MonadCatchIO m) => Query -> b -> (b -> row -> IO b) -> m b Source

forEach :: (HasMysql m, QueryResults r, QueryParams q, MonadCatchIO m) => Query -> q -> (r -> IO ()) -> m () Source

forEach_ :: (HasMysql m, QueryResults r, MonadCatchIO m) => Query -> (r -> IO ()) -> m () 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.MySQL.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 ?" (In [3,4,5])

Constructors

In a 

Instances

Functor In 
Eq a => Eq (In a) 
Ord a => Ord (In a) 
Read a => Read (In a) 
Show a => Show (In a) 
Param a => Param (In [a]) 
Typeable (* -> *) In 

newtype Binary a :: * -> *

Wrap a mostly-binary string to be escaped in hexadecimal.

Constructors

Binary a 

Instances

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 
Eq a => Eq (Only a) 
Ord a => Ord (Only a) 
Read a => Read (Only a) 
Show a => Show (Only a) 
Param a => QueryParams (Only a) 
Result a => QueryResults (Only a) 
Typeable (* -> *) Only 

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.

class QueryResults a where

A collection type that can be converted from a list of strings.

Instances should use the convert method of the Result class to perform conversion of each element of the collection.

This example instance demonstrates how to convert a two-column row into a Haskell pair. Each field in the metadata is paired up with each value from the row, and the two are passed to convert.

instance (Result a, Result b) => QueryResults (a,b) where
    convertResults [fa,fb] [va,vb] = (a,b)
        where !a = convert fa va
              !b = convert fb vb
    convertResults fs vs  = convertError fs vs 2

Notice that this instance evaluates each element to WHNF before constructing the pair. By doing this, we guarantee two important properties:

  • Keep resource usage under control by preventing the construction of potentially long-lived thunks.
  • Ensure that any ResultError that might arise is thrown immediately, rather than some place later in application code that cannot handle it.

You can also declare Haskell types of your own to be instances of QueryResults.

data User = User { firstName :: String, lastName :: String }

instance QueryResults User where
    convertResults [fa,fb] [va,vb] = User $ a * b
        where !a = convert fa va
              !b = convert fb vb
    convertResults fs vs  = convertError fs vs 2
 

Methods

convertResults :: [Field] -> [Maybe ByteString] -> a

Convert values from a row into a Haskell collection.

This function will throw a ResultError if conversion of the collection fails.

Instances

QueryResults AuthUser 
Result a => QueryResults (Only a) 
(Result a, Result b) => QueryResults (a, b) 
(Result a, Result b, Result c) => QueryResults (a, b, c) 
(Result a, Result b, Result c, Result d) => QueryResults (a, b, c, d) 
(Result a, Result b, Result c, Result d, Result e) => QueryResults (a, b, c, d, e) 
(Result a, Result b, Result c, Result d, Result e, Result f) => QueryResults (a, b, c, d, e, f) 
(Result a, Result b, Result c, Result d, Result e, Result f, Result g) => QueryResults (a, b, c, d, e, f, g) 
(Result a, Result b, Result c, Result d, Result e, Result f, Result g, Result h) => QueryResults (a, b, c, d, e, f, g, h) 
(Result a, Result b, Result c, Result d, Result e, Result f, Result g, Result h, Result i) => QueryResults (a, b, c, d, e, f, g, h, i) 
(Result a, Result b, Result c, Result d, Result e, Result f, Result g, Result h, Result i, Result j) => QueryResults (a, b, c, d, e, f, g, h, i, j) 

class QueryParams 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

renderParams :: a -> [Action]

Render a collection of values.

Instances

QueryParams () 
Param a => QueryParams [a] 
Param a => QueryParams (Only a) 
(Param a, Param b) => QueryParams (a, b) 
(Param a, Param b, Param c) => QueryParams (a, b, c) 
(Param a, Param b, Param c, Param d) => QueryParams (a, b, c, d) 
(Param a, Param b, Param c, Param d, Param e) => QueryParams (a, b, c, d, e) 
(Param a, Param b, Param c, Param d, Param e, Param f) => QueryParams (a, b, c, d, e, f) 
(Param a, Param b, Param c, Param d, Param e, Param f, Param g) => QueryParams (a, b, c, d, e, f, g) 
(Param a, Param b, Param c, Param d, Param e, Param f, Param g, Param h) => QueryParams (a, b, c, d, e, f, g, h) 
(Param a, Param b, Param c, Param d, Param e, Param f, Param g, Param h, Param i) => QueryParams (a, b, c, d, e, f, g, h, i) 
(Param a, Param b, Param c, Param d, Param e, Param f, Param g, Param h, Param i, Param j) => QueryParams (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
  • User root
  • No password
  • Database test
  • Character set utf8

Use as in the following example:

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