mysql-simple-quasi-1.0.0.0: Quasi-quoter for use with mysql-simple.

Safe HaskellNone

Database.MySQL.Simple.Quasi

Contents

Synopsis

Motivation

So, you want to access a MySQL database from Haskell. In an ideal world, your database schema would be known in its entirety to the compiler, and your MySQL queries would be fully parsed at compile-time and type-checked.

In reality, constructing a full parser for a MySQL query is a huge job, as is creating an EDSL for MySQL queries. But, still, the mysql-simple package by itself is a little too type-unsafe. For example, there's nothing stopping you writing this:

 (a, b) <- query conn "select a, b, c from table where id = ? and name = ?" (True, "x", 7)

That is: there's no guarantee that the number of params or results in the query matches the number you try to pass in/receive out of the query call. Additionally, there's no type checking on the inputs or outputs to the query.

Description

This module provides a quasi-quoter that is a half-way house between mysql-simple and a full-on database library/EDSL. You write your queries as a quasi-quote, and provide type annotations in the query itself. So for the previous example you would instead write:

 (a, b) <- query [qquery|select a{Int}, b{Bool}, c{Maybe String} from table where id = ?{Int} and name = ?{String}"|] (True, "x", 7)

You would then receive two type errors. One that your tuple (a, b) does not match (Int, Bool, Maybe String), and the other that (True, "x", 7) does not match (Int, String).

So, using the qquery quasi-quoter gives the following benefits:

  • It types the query with the annotated return type (and if any ? are used, the param types).
  • It automatically chooses to use QQuery or QQuery_ based on whether there are ? present.
  • It automatically wraps/unwraps Only types that mysql-simple uses to disambiguate its instances (but introduces no amibiguity).
  • It prevents splicing together strings to make a query. You must provide the entire query in one literal, and use wildcards to adjust any values. (I think this is a benefit, right? Enforced discipline.)

One technique that I find useful to combine with this quasi-quoter is typing integer keys differently. For example, let's say that you have two tables, "users" and "locations", each with an "id" field. You want an inner join of these tables where the "id"s are less than a given amount. If you use say, Int32, you can easily get confused, even with this quasi-quoter:

 (loc, user) {- mistake -} <- [qquery|select users.id{Int32}, locations.id{Int32}
   from users inner join locations
   where users.location_type = locations.type and users.id < ?{Int32} and locations.id < ?{Int32}|]
     (locIdThreshold, userIdThreshold) {- mistake -}

If instead you type them differently (with the appropriate instances), you will get two errors when doing this:

 newtype UserId = UserId Int
 newtype LocationId = LocationId Int
 (loc, user) {- mistake -} <- [qquery|select users.id{UserId}, locations.id{LocationId}
   from users inner join locations
   where users.location_type = locations.type and users.id < ?{UserId} and locations.id < ?{LocationId}|]
     (locIdThreshold, userIdThreshold) {- mistake -}

Quasi-Quoters

qquery :: QuasiQuoter

A quasi-quoter that takes the param and result types from the query string and generates a typed query. For example:

 [qquery|select * from users|]

will turn into an expression of type QueryResults r => QQuery_ r. This is not particularly useful. However, this:

 [qquery|select id{Int32}, name{String} from users|]

becomes QQuery_ (Int32, String).

Furthermore, this:

 [qquery|select id{Int32} from users where name = ?{String}|]

becomes: QQuery String Int32. And this:

 [qquery| select a.*{Int, Maybe String, String}, b.value{Double}
            from a inner join b on a.id = b.id
            where a.name = ?{String} and b.num = ?{Int}|]

becomes: QQuery (String, Int) (Int, Maybe String, String, Double).

In general:

  • Any non-escaped question mark in the String is taken to be one substitution. It is given type QueryParam a => a unless it is followed immediately (no spaces) by curly brackets with a type in it, in which case it uses that type.
  • A question mark preceded by a backslash is turned into a single question mark.
  • To insert an actual backslash, use double backslash.
  • Any other instances of curly brackets in the String are taken to be a comma-separated list of result types, which are all tupled (in the order they appear in the String) into a single result type. To get a literal curly bracket, put a backslash before it.
  • If there is only a single substitution or single result, Only is automatically added/removed when passing it through to the mysql-simple library.
  • If there is no ? substitution in the query, the resulting type is QQuery_ r. If there are substitutions, the resulting type is QQuery q r.

qexec :: QuasiQuoter

Same as qquery, except that it produces a query of type QExecute/QExecute_ instead of QQuery/QQuery_, and it gives an error if there are any result annotations (since executes don't return any results).

Query Types

data QQuery q r

A select-like query that takes q as its parameters and returns a list of r as its results.

Instances

data QQuery_ r

A select-like query that has no parameters, and returns a list of r as its results.

Instances

data QExecute q

An execute-like query that takes q as its parameters.

Instances

data QExecute_

An execute-like query that has no parameters. There's very little gain in using this over using execute_ from mysql-simple directly, but it's provided for completeness.

Running queries

execute :: Connection -> QExecute q -> q -> IO Int64

A wrapper for mysql-simple's execute function.

Note that no instances are required for q because the QExecute type witnesses them at its construction.

execute_ :: Connection -> QExecute_ -> IO Int64

A wrapper for mysql-simple's execute_ function.

executeMany :: Connection -> QExecute q -> [q] -> IO Int64

A wrapper for mysql-simple's executeMany function.

Note that no instances are required for q because the QExecute type witnesses them at its construction.

fold :: Connection -> QQuery q r -> q -> a -> (a -> r -> IO a) -> IO a

A wrapper for mysql-simple's fold function.

Note that no instances are required for q or r because the QQuery type witnesses them at its construction.

fold_ :: Connection -> QQuery_ r -> a -> (a -> r -> IO a) -> IO a

A wrapper for mysql-simple's fold_ function.

Note that no instances are required for r because the QQuery_ type witnesses them at its construction.

forEach :: Connection -> QQuery q r -> q -> (r -> IO ()) -> IO ()

A wrapper for mysql-simple's forEach function.

Note that no instances are required for q or r because the QQuery type witnesses them at its construction.

forEach_ :: Connection -> QQuery_ r -> (r -> IO ()) -> IO ()

A wrapper for mysql-simple's forEach_ function.

Note that no instances are required for r because the QQuery_ type witnesses them at its construction.

query :: Connection -> QQuery q r -> q -> IO [r]

A wrapper for mysql-simple's query function.

Note that no instances are required for q or r because the QQuery type witnesses them at its construction.

query_ :: Connection -> QQuery_ r -> IO [r]

A wrapper for mysql-simple's query_ function.

Note that no instances are required for r because the QQuery_ type witnesses them at its construction.

Internal access

class QExtractable q where

Methods

extractQuery :: q -> String

Extracts the query. This loses all the type safety of the original query and the whole point of using the library, but presumably you know what you're doing.