mysql-simple-0.4.9: A mid-level MySQL client library.
Copyright(c) 2011 MailRank Inc.
LicenseBSD3
MaintainerPaul Rouse <pyr@doynton.org>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.MySQL.Simple

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 :: IO Int
hello = do
  conn <- connect defaultConnectInfo
  [Only i] <- query_ conn "select 2 + 2"
  return i

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.

Finally, remember that the compiler must be able to infer the type of a query's results as well as its parameters. We might like the following example to work:

print =<< query_ conn "select 2 + 2"

Unfortunately, while a quick glance tells us that the result type should be a single row containing a single numeric column, the compiler has no way to infer what the types are. We can easily fix this by providing an explicit type annotation:

xs <- query_ conn "select 2 + 2"
print (xs :: [Only Int])

Substituting a single parameter

Haskell lacks a single-element tuple type, so if you have just one value you want substituted into a query or a single-column result, 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"]

A row of n query results is represented using an n-tuple, so you should use Only to represent a single-column result.

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')

Extracting results

The query and query_ functions return a list of values in the QueryResults typeclass. This class performs automatic extraction and type conversion of rows from a query result.

Here is a simple example of how to extract results:

import qualified Data.Text as Text

xs <- query_ conn "select name,age from users"
forM_ xs $ \(name,age) ->
  putStrLn $ Text.unpack name ++ " is " ++ show (age :: Int)

Notice two important details about this code:

  • The number of columns we ask for in the query template must exactly match the number of elements we specify in a row of the result tuple. If they do not match, a ResultError exception will be thrown.
  • Sometimes, the compiler needs our help in specifying types. It can infer that name must be a Text, due to our use of the unpack function. However, we have to tell it the type of age, as it has no other information to determine the exact type.

Handling null values

The type of a result tuple will look something like this:

(Text, Int, Int)

Although SQL can accommodate NULL as a value for any of these types, Haskell cannot. If your result contains columns that may be NULL, be sure that you use Maybe in those positions of of your tuple.

(Text, Maybe Int, Int)

If query encounters a NULL in a row where the corresponding Haskell type is not Maybe, it will throw a ResultError exception.

Type conversions

Conversion of SQL values to Haskell values is somewhat permissive. Here are the rules.

  • For numeric types, any Haskell type that can accurately represent all values of the given MySQL type is considered "compatible". For instance, you can always extract a MySQL TINYINT column to a Haskell Int. The Haskell Float type can accurately represent MySQL integer types of size up to INT24, so it is considered compatible with those types.
  • A numeric compatibility check is based only on the type of a column, not on its values. For instance, a MySQL LONG_LONG column will be considered incompatible with a Haskell Int8, even if it contains the value 1.
  • If a numeric incompatibility is found, query will throw a ResultError.
  • The String and Text types are assumed to be encoded as UTF-8. If you use some other encoding, decoding may fail or give wrong results. In such cases, write a newtype wrapper and a custom Result instance to handle your encoding.

When a user-defined type is represented by a TEXT, BLOB, JSON, or similar type of column, it can be encoded and decoded using hooks which take or receive a ByteString. See the classes ToField and FromField in the Extension hooks section below.

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

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

Instances

Instances details
IsString Query Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

fromString :: String -> Query #

Monoid Query Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

mempty :: Query #

mappend :: Query -> Query -> Query #

mconcat :: [Query] -> Query #

Semigroup Query Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

(<>) :: Query -> Query -> Query #

sconcat :: NonEmpty Query -> Query #

stimes :: Integral b => b -> Query -> Query #

Read Query Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Show Query Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Eq Query Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

(==) :: Query -> Query -> Bool #

(/=) :: Query -> Query -> Bool #

Ord Query Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

compare :: Query -> Query -> Ordering #

(<) :: Query -> Query -> Bool #

(<=) :: Query -> Query -> Bool #

(>) :: Query -> Query -> Bool #

(>=) :: Query -> Query -> Bool #

max :: Query -> Query -> Query #

min :: Query -> Query -> Query #

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 c "select * from whatever where id in ?" (Only (In [3,4,5]))

Constructors

In a 

Instances

Instances details
Functor In Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

fmap :: (a -> b) -> In a -> In b #

(<$) :: a -> In b -> In a #

Read a => Read (In a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Show a => Show (In a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

showsPrec :: Int -> In a -> ShowS #

show :: In a -> String #

showList :: [In a] -> ShowS #

Eq a => Eq (In a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

(==) :: In a -> In a -> Bool #

(/=) :: In a -> In a -> Bool #

Ord a => Ord (In a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

compare :: In a -> In a -> Ordering #

(<) :: In a -> In a -> Bool #

(<=) :: In a -> In a -> Bool #

(>) :: In a -> In a -> Bool #

(>=) :: In a -> In a -> Bool #

max :: In a -> In a -> In a #

min :: In a -> In a -> In a #

Param a => Param (In (Set a)) Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: In (Set a) -> Action Source #

Param a => Param (In [a]) Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: In [a] -> Action Source #

newtype VaArgs a Source #

Wrap a list of values for use in a function with variable arguments. Replaces a single "?" character with a non-parenthesized list of rendered values.

Example:

query conn
  "SELECT * FROM example_table ORDER BY field(f,?)"
  (Only (VaArgs [3,2,1]))

Constructors

VaArgs a 

Instances

Instances details
Functor VaArgs Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

fmap :: (a -> b) -> VaArgs a -> VaArgs b #

(<$) :: a -> VaArgs b -> VaArgs a #

Read a => Read (VaArgs a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Show a => Show (VaArgs a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

showsPrec :: Int -> VaArgs a -> ShowS #

show :: VaArgs a -> String #

showList :: [VaArgs a] -> ShowS #

Eq a => Eq (VaArgs a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

(==) :: VaArgs a -> VaArgs a -> Bool #

(/=) :: VaArgs a -> VaArgs a -> Bool #

Ord a => Ord (VaArgs a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

compare :: VaArgs a -> VaArgs a -> Ordering #

(<) :: VaArgs a -> VaArgs a -> Bool #

(<=) :: VaArgs a -> VaArgs a -> Bool #

(>) :: VaArgs a -> VaArgs a -> Bool #

(>=) :: VaArgs a -> VaArgs a -> Bool #

max :: VaArgs a -> VaArgs a -> VaArgs a #

min :: VaArgs a -> VaArgs a -> VaArgs a #

Param a => Param (VaArgs [a]) Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: VaArgs [a] -> Action Source #

newtype Binary a Source #

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

Constructors

Binary a 

Instances

Instances details
Functor Binary Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

fmap :: (a -> b) -> Binary a -> Binary b #

(<$) :: a -> Binary b -> Binary a #

Read a => Read (Binary a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Show a => Show (Binary a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

showsPrec :: Int -> Binary a -> ShowS #

show :: Binary a -> String #

showList :: [Binary a] -> ShowS #

Eq a => Eq (Binary a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

(==) :: Binary a -> Binary a -> Bool #

(/=) :: Binary a -> Binary a -> Bool #

Ord a => Ord (Binary a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

compare :: Binary a -> Binary a -> Ordering #

(<) :: Binary a -> Binary a -> Bool #

(<=) :: Binary a -> Binary a -> Bool #

(>) :: Binary a -> Binary a -> Bool #

(>=) :: Binary a -> Binary a -> Bool #

max :: Binary a -> Binary a -> Binary a #

min :: Binary a -> Binary a -> Binary a #

Param (Binary ByteString) Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Param (Binary ByteString) Source # 
Instance details

Defined in Database.MySQL.Simple.Param

newtype Only a Source #

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

Instances

Instances details
Functor Only Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

fmap :: (a -> b) -> Only a -> Only b #

(<$) :: a -> Only b -> Only a #

Read a => Read (Only a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Show a => Show (Only a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

showsPrec :: Int -> Only a -> ShowS #

show :: Only a -> String #

showList :: [Only a] -> ShowS #

Eq a => Eq (Only a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

(==) :: Only a -> Only a -> Bool #

(/=) :: Only a -> Only a -> Bool #

Ord a => Ord (Only a) Source # 
Instance details

Defined in Database.MySQL.Simple.Types

Methods

compare :: Only a -> Only a -> Ordering #

(<) :: Only a -> Only a -> Bool #

(<=) :: Only a -> Only a -> Bool #

(>) :: Only a -> Only a -> Bool #

(>=) :: Only a -> Only a -> Bool #

max :: Only a -> Only a -> Only a #

min :: Only a -> Only a -> Only a #

Param a => QueryParams (Only a) Source # 
Instance details

Defined in Database.MySQL.Simple.QueryParams

Methods

renderParams :: Only a -> [Action] Source #

Result a => QueryResults (Only a) Source # 
Instance details

Defined in Database.MySQL.Simple.QueryResults

class Param a Source #

A type that may be used as a single parameter to a SQL query.

A default implementation is provided for any type which is an instance of ToField, providing a simple mechanism for user-defined encoding to text- or blob-like fields (including JSON).

Instances

Instances details
Param Int16 Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Int16 -> Action Source #

Param Int32 Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Int32 -> Action Source #

Param Int64 Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Int64 -> Action Source #

Param Int8 Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Int8 -> Action Source #

Param Word16 Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Word16 -> Action Source #

Param Word32 Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Word32 -> Action Source #

Param Word64 Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Word64 -> Action Source #

Param ByteString Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Param ByteString Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Param Action Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Action -> Action Source #

Param Null Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Null -> Action Source #

Param Text Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Text -> Action Source #

Param Text Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Text -> Action Source #

Param Day Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Day -> Action Source #

Param UTCTime Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Param TimeOfDay Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Param Word8 Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Word8 -> Action Source #

Param Integer Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Param Bool Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Bool -> Action Source #

Param Double Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Double -> Action Source #

Param Float Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Float -> Action Source #

Param Int Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Int -> Action Source #

Param Word Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Word -> Action Source #

Param (Binary ByteString) Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Param (Binary ByteString) Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Param a => Param (In (Set a)) Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: In (Set a) -> Action Source #

Param a => Param (In [a]) Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: In [a] -> Action Source #

Param a => Param (VaArgs [a]) Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: VaArgs [a] -> Action Source #

Param a => Param (Maybe a) Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: Maybe a -> Action Source #

Param [Char] Source # 
Instance details

Defined in Database.MySQL.Simple.Param

Methods

render :: [Char] -> Action Source #

class Result a Source #

A type that may be converted from a SQL type.

A default implementation is provided for any type which is an instance of both FromField and Typeable, providing a simple mechanism for user-defined decoding from text- or blob-like fields (including JSON).

Instances

Instances details
Result Int16 Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Int32 Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Int64 Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Int8 Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Word16 Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Word32 Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Word64 Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result ByteString Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result ByteString Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Text Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Text Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Day Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result UTCTime Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result TimeOfDay Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Word8 Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Integer Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Bool Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Double Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Float Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Int Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result Word Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result (Ratio Integer) Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result a => Result (Maybe a) Source # 
Instance details

Defined in Database.MySQL.Simple.Result

Result [Char] Source # 
Instance details

Defined in Database.MySQL.Simple.Result

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.

When processing large results, this function will consume a lot of client-side memory. Consider using fold instead.

Exceptions that may be thrown:

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

A version of query that does not perform query substitution.

Queries that stream results

fold Source #

Arguments

:: (QueryParams q, QueryResults r) 
=> Connection 
-> Query

Query template.

-> q

Query parameters.

-> a

Initial state for result consumer.

-> (a -> r -> IO a)

Result consumer.

-> IO a 

Perform a SELECT or other SQL query that is expected to return results. Results are streamed incrementally from the server, and consumed via a left fold.

The result consumer must be carefully written to execute quickly. If the consumer is slow, server resources will be tied up, and other clients may not be able to update the tables from which the results are being streamed.

When dealing with small results, it may be simpler (and perhaps faster) to use query instead.

This fold is not strict. The stream consumer is responsible for forcing the evaluation of its result to avoid space leaks.

Exceptions that may be thrown:

fold_ Source #

Arguments

:: QueryResults r 
=> Connection 
-> Query

Query.

-> a

Initial state for result consumer.

-> (a -> r -> IO a)

Result consumer.

-> IO a 

A version of fold that does not perform query substitution.

forEach Source #

Arguments

:: (QueryParams q, QueryResults r) 
=> Connection 
-> Query

Query template.

-> q

Query parameters.

-> (r -> IO ())

Result consumer.

-> IO () 

A version of fold that does not transform a state value.

forEach_ Source #

Arguments

:: QueryResults r 
=> Connection 
-> Query

Query template.

-> (r -> IO ())

Result consumer.

-> IO () 

A version of forEach that does not perform query substitution.

Statements that do not return results

execute :: QueryParams q => Connection -> Query -> q -> IO Int64 Source #

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 Int64 Source #

A version of execute that does not perform query substitution.

executeMany :: QueryParams q => Connection -> Query -> [q] -> IO Int64 Source #

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 a Source #

Execute an action inside a SQL transaction.

This function initiates a transaction with a "begin transaction" statement, then executes the supplied action. If the action succeeds, the transaction will be completed with commit before this function returns.

If the action throws any kind of exception (not just a MySQL-related exception), the transaction will be rolled back using rollback, then the exception will be rethrown.

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 ByteString Source #

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 ByteString Source #

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.

splitQuery :: ByteString -> [Builder] Source #

Split a query into fragments separated by ? characters. Does not break a fragment if the question mark is in a string literal.

Extension hooks

These classes provide a simple mechanism for encoding and decoding user-defined types in cases where the underlying encoding is a sequence of bytes.

Example

Expand

Assuming Foo has instances of FromJSON, ToJSON, and Typeable, its decoding and encoding can be specified like this:

instance FromField Foo where
    fromField = ([Database.MySQL.Base.Types.Json], Data.Aeson.eitherDecodeStrict')
instance Result Foo

instance ToField Foo where
    toField = Data.ByteString.Lazy.toStrict . Data.Aeson.encode
instance Param Foo

class FromField a where Source #

A type that can be converted from a ByteString. Any type which is an instance of this class, and is Typeable, can use the default implementation of Result. This provides a method of implementing a decoder for any text-like column, such as TEXT, BLOB, or JSON, instead of implementing Result directly.

The first component of the tuple returned by fromField is a list of acceptable column types, expressed in terms of Type.

Since: 0.4.8

Instances

Instances details
FromField UTCTime Source # 
Instance details

Defined in Database.MySQL.Simple.Result

FromField TimeOfDay Source # 
Instance details

Defined in Database.MySQL.Simple.Result

class ToField a where Source #

A type that can be converted to a ByteString for use as a parameter to an SQL query.

Any type which is an instance of this class can use the default implementation of Param, which will wrap encodings with Escape.

Since: 0.4.8

Methods

toField :: a -> ByteString Source #