mysql-simple-0.2.0.1: A mid-level MySQL client library.

Portabilityportable
Stabilityexperimental
MaintainerBryan O'Sullivan <bos@mailrank.com>

Database.MySQL.Simple

Contents

Description

A mid-level client library for the MySQL database, aimed at ease of use and high performance.

Synopsis

Writing queries

SQL-based applications are somewhat notorious for their susceptibility to attacks through the injection of maliciously crafted data. The primary reason for widespread vulnerability to SQL injections is that many applications are sloppy in handling user data when constructing SQL queries.

This library provides a Query type and a parameter substitution facility to address both ease of use and security.

The Query type

A Query is a newtype-wrapped ByteString. It intentionally exposes a tiny API that is not compatible with the ByteString API; this makes it difficult to construct queries from fragments of strings. The query and execute functions require queries to be of type Query.

To most easily construct a query, enable GHC's OverloadedStrings language extension and write your query as a normal literal string.

 {-# LANGUAGE OverloadedStrings #-}

 import Database.MySQL.Simple

 hello = do
   conn <- connect defaultConnectInfo
   query conn "select 2 + 2"

A Query value does not represent the actual query that will be executed, but is a template for constructing the final query.

Parameter substitution

Since applications need to be able to construct queries with parameters that change, this library provides a query substitution capability.

The Query template accepted by query and execute can contain any number of "?" characters. Both query and execute accept a third argument, typically a tuple. When constructing the real query to execute, these functions replace the first "?" in the template with the first element of the tuple, the second "?" with the second element, and so on. If necessary, each tuple element will be quoted and escaped prior to substitution; this defeats the single most common injection vector for malicious data.

For example, given the following Query template:

 select * from user where first_name = ? and age > ?

And a tuple of this form:

 ("Boris" :: String, 37 :: Int)

The query to be executed will look like this after substitution:

 select * from user where first_name = 'Boris' and age > 37

If there is a mismatch between the number of "?" characters in your template and the number of elements in your tuple, a FormatError will be thrown.

Note that the substitution functions do not attempt to parse or validate your query. It's up to you to write syntactically valid SQL, and to ensure that each "?" in your query template is matched with the right tuple element.

Type inference

Automated type inference means that you will often be able to avoid supplying explicit type signatures for the elements of a tuple. However, sometimes the compiler will not be able to infer your types. Consider a care where you write a numeric literal in a parameter tuple:

 query conn "select ? + ?" (40,2)

The above query will be rejected by the compiler, because it does not know the specific numeric types of the literals 40 and 2. This is easily fixed:

 query conn "select ? + ?" (40 :: Double, 2 :: Double)

The same kind of problem can arise with string literals if you have the OverloadedStrings language extension enabled. Again, just use an explicit type signature if this happens.

Substituting a single parameter

Haskell lacks a single-element tuple type, so if you have just one value you want substituted into a query, what should you do?

The obvious approach would appear to be something like this:

 instance (Param a) => QueryParam a where
     ...

Unfortunately, this wreaks havoc with type inference, so we take a different tack. To represent a single value val as a parameter, write a singleton list [val], use Just val, or use Only val.

Here's an example using a singleton list:

 execute conn "insert into users (first_name) values (?)"
              ["Nuala"]

Representing a list of values

Suppose you want to write a query using an IN clause:

 select * from users where first_name in ('Anna', 'Boris', 'Carla')

In such cases, it's common for both the elements and length of the list after the IN keyword to vary from query to query.

To address this case, use the In type wrapper, and use a single "?" character to represent the list. Omit the parentheses around the list; these will be added for you.

Here's an example:

 query conn "select * from users where first_name in ?" $
       In ["Anna", "Boris", "Carla"]

If your In-wrapped list is empty, the string "(null)" will be substituted instead, to ensure that your clause remains syntactically valid.

Modifying multiple rows at once

If you know that you have many rows of data to insert into a table, it is much more efficient to perform all the insertions in a single multi-row INSERT statement than individually.

The executeMany function is intended specifically for helping with multi-row INSERT and UPDATE statements. Its rules for query substitution are different than those for execute.

What executeMany searches for in your Query template is a single substring of the form:

 values (?,?,?)

The rules are as follows:

  • The keyword VALUES is matched case insensitively.
  • There must be no other "?" characters anywhere in your template.
  • There must one or more "?" in the parentheses.
  • Extra white space is fine.

The last argument to executeMany is a list of parameter tuples. These will be substituted into the query where the (?,?) string appears, in a form suitable for use in a multi-row INSERT or UPDATE..

Here is an example:

 executeMany conn
   "insert into users (first_name,last_name) values (?,?)"
   [("Boris","Karloff"),("Ed","Wood")]

The query that will be executed here will look like this (reformatted for tidiness):

 insert into users (first_name,last_name) values
   ('Boris','Karloff'),('Ed','Wood')

Types

data Connection

Connection to a MySQL database.

data Query Source

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 ?"

newtype In a Source

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

Example:

 query "select * from whatever where id in ?" (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) 
Param a => Param (In [a]) 

newtype Only a Source

A single-value collection.

This can be handy if you need to supply a single parameter to a SQL query.

Example:

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

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) 
Result a => QueryResults (Only a) 
Param a => QueryParams (Only a) 

Exceptions

data FormatError Source

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 Source

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

data ResultError Source

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

Connection management

connect :: ConnectInfo -> IO Connection

Connect to a database.

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" }

close :: Connection -> IO ()

Close a connection, and mark any outstanding Result as invalid.

Queries that return results

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

Perform a SELECT or other SQL query that is expected to return results.

All results are retrieved and converted before this function returns.

Exceptions that may be thrown:

query_ :: QueryResults r => Connection -> Query -> IO [r]Source

A version of query that does not perform query substitution.

Statements that do not return results

execute :: QueryParams q => Connection -> Query -> q -> IO Int64Source

Execute an INSERT, UPDATE, or other SQL query that is not expected to return results.

Returns the number of rows affected.

Throws FormatError if the query could not be formatted correctly.

execute_ :: Connection -> Query -> IO Int64Source

A version of execute that does not perform query substitution.

executeMany :: QueryParams q => Connection -> Query -> [q] -> IO Int64Source

Execute a multi-row INSERT, UPDATE, or other SQL query that is not expected to return results.

Returns the number of rows affected.

Throws FormatError if the query could not be formatted correctly.

insertID :: Connection -> IO Word64

Return the value generated for an AUTO_INCREMENT column by the previous INSERT or UPDATE statement.

See http://dev.mysql.com/doc/refman/5.5/en/mysql-insert-id.html

Transaction handling

withTransaction :: Connection -> IO a -> IO aSource

Execute an action inside a SQL transaction.

You are assumed to have started the transaction yourself.

If your action succeeds, the transaction will be committed before this function returns.

If your action throws any exception (not just a SQL exception), the transaction will be rolled back rollback before the exception is propagated.

autocommit :: Connection -> Bool -> IO ()

Turn autocommit on or off.

By default, MySQL runs with autocommit mode enabled. In this mode, as soon as you modify a table, MySQL stores your modification permanently.

commit :: Connection -> IO ()

Commit the current transaction.

rollback :: Connection -> IO ()

Roll back the current transaction.

Helper functions

formatMany :: QueryParams q => Connection -> Query -> [q] -> IO ByteStringSource

Format a query string with a variable number of rows.

This function is exposed to help with debugging and logging. Do not use it to prepare queries for execution.

The query string must contain exactly one substitution group, identified by the SQL keyword "VALUES" (case insensitive) followed by an "(" character, a series of one or more "?" characters separated by commas, and a ")" character. White space in a substitution group is permitted.

Throws FormatError if the query string could not be formatted correctly.

formatQuery :: QueryParams q => Connection -> Query -> q -> IO ByteStringSource

Format a query string.

This function is exposed to help with debugging and logging. Do not use it to prepare queries for execution.

String parameters are escaped according to the character set in use on the Connection.

Throws FormatError if the query string could not be formatted correctly.