yeshql-0.2.0.0: YesQL-style SQL database abstraction

Copyright(c) 2015 Tobias Dammers
MaintainerTobias Dammers <tdammers@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Database.YeshQL

Contents

Description

License: MIT

Unlike existing libraries such as Esqueleto or Persistent, YeshQL does not try to provide full SQL abstraction with added type safety; instead, it gives you some simple tools to write the SQL queries yourself and bind them to (typed) functions.

Usage

The main workhorses are the yesh1 (to define one query) and yesh (to define multiple queries) quasi-quoters.

Both yesh and yesh1 can produce either declarations or expressions, depending on the context in which they are used.

Creating Declarations

When used at the top level, or inside a where block, the yesh and yesh1 quasi-quoters will declare one or more functions, according to the query names given in the query definition. Example:

[yesh1|
    -- name:insertUser :: (Integer)
    -- :name :: String
    INSERT INTO users (name) VALUES (:name) RETURNING id |]

...will create a top-level function of type:

    insertUser :: IConnection conn => conn -> String -> IO [Integer]

Syntax

Because SQL itself does not *quite* provide enough information to generate a fully typed Haskell function, we extend SQL syntax a bit.

Here's what a typical YeshQL definition looks like:

[yesh|
    -- name:insertUser :: (Integer)
    -- :name :: String
    INSERT INTO users (name) VALUES (:name) RETURNING id;
    -- name:deleteUser :: Integer
    -- :id :: Integer
    DELETE FROM users WHERE id = :id;
    -- name:getUser :: (Integer, String)
    -- :id :: Integer
    SELECT id, name FROM users WHERE id = :id;
    -- name:getUserEx :: (Integer, String)
    -- :id :: Integer
    -- :filename :: String
    SELECT id, name FROM users WHERE name = :filename OR id = :id;
    |]

On top of standard SQL syntax, YeshQL query definitions are preceded by some extra information in order to generate well-typed HDBC queries. All that information is written in SQL line comments (-- ...), such that a valid YeshQL definition is also valid SQL by itself (with the exception of parameters, which follow the pattern :paramName).

Let's break it down:

    -- name:insertUser :: (Integer)

This line tells YeshQL to generate an object called insertUser, which should be a function of type IConnection conn => conn -> {...} -> IO (Integer) (where the {...} part depends on query parameters, see below).

The declared return type can be one of the following:

  • '()'; the generated function will ignore any and all results from the query and always return '()'.
  • An integer scalar, e.g. Integer or Int; the generated function will return a row count from INSERT UPDATE ... statements, or 0 from SELECT statements.
  • A tuple, where all elements implement FromSql; the function will return the result set from a SELECT query as a list of tuples, or an empty list for other query types.
  • A "one-tuple", i.e., a type in parentheses. The return value will be a list of scalars, containing the values from the first (or only) column in the result set. Note that, unlike Haskell, YeshQL does distinguish between Type and (Type): the former is a scalar type, while the latter is a one-tuple whose only element is of type Type.
    -- :paramName :: Type

Declares a Haskell type for a parameter. The parameter :paramName can then be referenced zero or more times in the query itself, and will appear in the generated function signature in the order of declaration. So in the above example, the last query definition:

    -- name:getUserEx :: (Integer, String)
    -- :id :: Integer
    -- :filename :: String
    SELECT id, name FROM users WHERE name = :filename OR id = :id;

...will produce the function:

getUserEx :: IConnection conn => conn -> Integer -> String -> IO [(Integer, String)]
getUserEx conn id filename =
    -- ... generated implementation left out

Loading Queries From External Files

The yeshFile and yesh1File flavors take a file name instead of SQL definition strings. Using these, you can put your SQL in external files rather than clutter your code with long quasi-quotation blocks.

Other Functions That YeshQL Generates

On top of the obvious query functions, a top-level YeshQL quasiquotation introduces two more definitions per query: a String variable prefixed describe-, which contains the SQL query as passed to HDBC (similar to the DESCRIBE feature in some RDBMS systems), and another String variable prefixed doc-, which contains all the free-form comments that precede the SQL query in the query definition.

So for example, this quasiquotation:

[yesh1|
    -- name:getUser :: (Integer, String)
    -- :userID :: Integer
    -- Gets one user by the "id" column.
    SELECT id, username FROM users WHERE id = :userID LIMIT 1 |]

...would produce the following three top-level definitions:

getUser :: IConnection conn => Integer -> conn -> [(Integer, String)]
getUser userID conn = ...

describeGetUser :: String
describeGetUser = "SELECT id, username FROM users WHERE id = ? LIMIT 1"

docGetUser :: String
docGetUser = "Gets one user by the \"id\" column."

Synopsis

Quasi-quoters that take strings

yesh :: QuasiQuoter Source

Generate top-level declarations or expressions for several SQL queries. If used at the top level (i.e., generating declarations), all queries in the definitions must be named, and yesh will generate a separate set of functions for each. If used in an expression context, the current behavior is somewhat undesirable, namely sequencing the queries using >>.

Future versions will most likely change this to create a tuple of query expressions instead, such that you can write something like:

let (createUser, getUser, updateUser, deleteUser) = [yesh|
     -- name:createUser :: (Integer)
     -- :username :: String
     INSERT INTO users (username) VALUES (:username) RETURNING id;
     -- name:getUser :: (Integer, String)
     -- :userID :: Integer
     SELECT id, username FROM users WHERE id = :userID;
     -- name:updateUser :: Integer
     -- :userID :: Integer
     -- :username :: String
     UPDATE users SET username = :username WHERE id = :userID;
     -- name:deleteUser :: Integer
     -- :userID :: Integer
     DELETE FROM users WHERE id = :userID LIMIT 1;
 |]

yesh1 :: QuasiQuoter Source

Generate a top-level declaration or an expression for a single SQL query. If used at the top level (i.e., generating a declaration), the query definition must specify a query name.

Quasi-quoters that take filenames

yeshFile :: QuasiQuoter Source

Generate multiple query definitions or expressions from an external file. Query name derivation works exactly like for yesh1File, except that an underscore and a 0-based query index are appended to disambiguate queries from the same file.

In an expression context, the same caveats apply as for yesh, i.e., to generate expressions, you will almost certainly want yesh1File, not yeshFile.

yesh1File :: QuasiQuoter Source

Generate one query definition or expression from an external file. In a declaration context, the query name will be derived from the filename unless the query contains an explicit name. Query name derivation works as follows:

  • Take only the basename (stripping off the directories and extension)
  • Remove all non-alphabetic characters from the beginning of the name
  • Remove all non-alphanumeric characters from the name
  • Lower-case the first character.

Note that since there is always a filename to derive the query name from, explicitly defining a query name is only necessary when you want it to differ from the filename; however, making it explicit anyway is probably a good idea.

Low-level generators in the Q monad

Query parsers

AST

data ParsedQuery Source

Constructors

ParsedQuery 

Fields

pqQueryName :: String
 
pqQueryString :: String
 
pqParamsRaw :: [(String, ParsedType)]
 
pqParamNames :: [String]
 
pqParamTypes :: Map String ParsedType
 
pqReturnType :: Either ParsedType [ParsedType]
 
pqDocComment :: String