esqueleto-0.2.1: Bare bones, type-safe EDSL for SQL queries on persistent backends.

Safe HaskellSafe-Infered

Database.Esqueleto

Contents

Description

The esqueleto EDSL (embedded domain specific language). This module replaces Database.Persist, so instead of importing that module you should just import this one:

 import Database.Esqueleto
 import qualified Database.Persist.Query as OldQuery

Synopsis

Setup

If you're already using persistent, then you're ready to use esqueleto, no further setup is needed. If you're just starting a new project and would like to use esqueleto, take a look at persistent's book first (http://www.yesodweb.com/book/persistent) to learn how to define your schema.

Introduction

The main goals of esqueleto are to:

  • Be easily translatable to SQL. When you take a look at a esqueleto query, you should be able to know exactly how the SQL query will end up. (As opposed to being a relational algebra EDSL such as HaskellDB, which is non-trivial to translate into SQL.)
  • Support the mostly used SQL features. We'd like you to be able to use esqueleto for all of your queries, no exceptions. Send a pull request or open an issue on our project page (https://github.com/meteficha/esqueleto) if there's anything missing that you'd like to see.
  • Be as type-safe as possible. There are ways of shooting yourself in the foot while using esqueleto because it's extremely hard to provide 100% type-safety into a SQL-like EDSL---there's a tension between supporting features with a nice syntax and rejecting bad code. However, we strive to provide as many type checks as possible. If you get bitten by some invalid code that type-checks, please open an issue on our project page so we can take a look.

Getting started

We like clean, easy-to-read EDSLs. However, in order to achieve this goal we've used a lot of type hackery, leading to some hard-to-read type signatures. On this section, we'll try to build some intuition about the syntax.

For the following examples, we'll use this example schema:

 share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persist|
   Person
     name String
     age Int Maybe
     deriving Eq Show
   BlogPost
     title String
     authorId PersonId
     deriving Eq Show
   Follow
     follower PersonId
     followed PersonId
     deriving Eq Show
 |]

Most of esqueleto was created with SELECT statements in mind, not only because they're the most common but also because they're the most complex kind of statement. The most simple kind of SELECT would be:

 SELECT *
 FROM Person

In esqueleto, we may write the same query above as:

 do people <- select $
              from $ \person -> do
              return person
    liftIO $ mapM_ (putStrLn . personName . entityVal) people

The expression above has type SqlPersist m (), while people has type [Entity Person]. The query above will be translated into exactly the same query we wrote manually, but instead of SELECT * it will list all entity fields (using * is not robust). Note that esqueleto knows that we want an Entity Person just because of the personName that we're printing later.

However, most of the time we need to filter our queries using WHERE. For example:

 SELECT *
 FROM Person
 WHERE Person.name = "John"

In esqueleto, we may write the same query above as:

 select $
 from $ \p -> do
 where_ (p ^. PersonName ==. val "John")
 return p

Although esqueleto's code is a bit more noisy, it's has almost the same structure (save from the return). The (^.) operator is used to project a field from an entity. The field name is the same one generated by persistent's Template Haskell functions. We use val to lift a constant Haskell value into the SQL query.

Another example would be:

 SELECT *
 FROM Person
 WHERE Person.age >= 18

In esqueleto, we may write the same query above as:

 select $
 from $ \p -> do
 where_ (p ^. PersonAge >=. just (val 18))
 return p

Since age is an optional Person field, we use just lift val 18 :: SqlExpr (Value Int) into just (val 18) :: SqlExpr (Value (Just Int)).

Implicit joins are represented by tuples. For example, to get the list of all blog posts and their authors, we could write:

 SELECT BlogPost.*, Person.*
 FROM BlogPost, Person
 WHERE BlogPost.authorId = Person.id
 ORDER BY BlogPost.title ASC

In esqueleto, we may write the same query above as:

 select $
 from $ \(b, p) -> do
 where_ (b ^. BlogPostAuthorId ==. p ^. PersonId)
 orderBy [asc (b ^. BlogPostTitle)]
 return (b, p)

However, we may want your results to include people who don't have any blog posts as well using a LEFT OUTER JOIN:

 SELECT Person.*, BlogPost.*
 FROM Person LEFT OUTER JOIN BlogPost
 ON Person.id = BlogPost.authorId
 ORDER BY Person.name ASC, BlogPost.title ASC

In esqueleto, we may write the same query above as:

 select $
 from $ \(p `LeftOuterJoin` mb) -> do
 on (just (p ^. PersonId) ==. mb ?. BlogPostAuthorId)
 orderBy [asc (p ^. PersonName), asc (mb ?. BlogPostTitle)]
 return (p, mb)

On a LEFT OUTER JOIN the entity on the right hand side may not exist (i.e. there may be a Person without any BlogPosts), so while p :: SqlExpr (Entity Person), we have mb :: SqlExpr (Maybe (Entity BlogPost)). The whole expression above has type SqlPersist m [(Entity Person, Maybe (Entity BlogPost))]. Instead of using (^.), we used (?.) to project a field from a Maybe (Entity a).

We are by no means limited to joins of two tables, nor by joins of different tables. For example, we may want a list the Follow entity:

 SELECT P1.*, Follow.*, P2.*
 FROM Person AS P1
 INNER JOIN Follow ON P1.id = Follow.follower
 INNER JOIN P2 ON P2.id = Follow.followed

In esqueleto, we may write the same query above as:

 select $
 from $ \(p1 `InnerJoin` f `InnerJoin` p2) -> do
 on (p2 ^. PersonId ==. f ^. FollowFollowed)
 on (p1 ^. PersonId ==. f ^. FollowFollower)
 return (p1, f, p2)

Note carefully that the order of the ON clauses is reversed! You're required to write your ons in reverse order because that helps composability (see the documention of on for more details).

We also currently supports UPDATE and DELETE statements. For example:

 do update $ \p -> do
      set p [ PersonName =. val "João" ]
      where_ (p ^. PersonName ==. val "Joao")
    delete $
      from $ \p -> do
      where_ (p ^. PersonAge <. just (val 14))

esqueleto's Language

class (Functor query, Applicative query, Monad query) => Esqueleto query expr backend | query -> expr backend, expr -> query backend whereSource

Finally tagless representation of esqueleto's EDSL.

Methods

where_ :: expr (Value Bool) -> query ()Source

WHERE clause: restrict the query's result.

on :: expr (Value Bool) -> query ()Source

ON clause: restrict the a JOIN's result. The ON clause will be applied to the last JOIN that does not have an ON clause yet. If there are no JOINs without ON clauses (either because you didn't do any JOIN, or because all JOINs already have their own ON clauses), a runtime exception OnClauseWithoutMatchingJoinException is thrown. ON clauses are optional when doing JOINs.

On the simple case of doing just one JOIN, for example

 select $
 from $ (foo InnerJoin bar) -> do
   on (foo ^. FooId ==. bar ^. BarFooId)
   ...

there's no ambiguity and the rules above just mean that you're allowed to call on only once (as in SQL). If you have many joins, then the ons are applied on the reverse order that the JOINs appear. For example:

 select $
 from $ (foo InnerJoin bar InnerJoin baz) -> do
   on (baz ^. BazId ==. bar ^. BarBazId)
   on (foo ^. FooId ==. bar ^. BarFooId)
   ...

The order is reversed in order to improve composability. For example, consider query1 and query2 below:

 let query1 =
       from $ (foo InnerJoin bar) -> do
         on (foo ^. FooId ==. bar ^. BarFooId)

query2 =
       from $ (mbaz LeftOuterJoin quux) -> do
         return (mbaz ?. BazName, quux)

test1 =      (,) $ query1 * query2
     test2 = flip (,) $ query2 * query1

If the order was *not* reversed, then test2 would be broken: query1's on would refer to query2's LeftOuterJoin.

orderBy :: [expr OrderBy] -> query ()Source

ORDER BY clause. See also asc and desc.

asc :: PersistField a => expr (Value a) -> expr OrderBySource

Ascending order of this field or expression.

desc :: PersistField a => expr (Value a) -> expr OrderBySource

Descending order of this field or expression.

sub_select :: PersistField a => query (expr (Value a)) -> expr (Value a)Source

Execute a subquery SELECT in an expression.

sub_selectDistinct :: PersistField a => query (expr (Value a)) -> expr (Value a)Source

Execute a subquery SELECT_DISTINCT in an expression.

(^.) :: (PersistEntity val, PersistField typ) => expr (Entity val) -> EntityField val typ -> expr (Value typ)Source

Project a field of an entity.

(?.) :: (PersistEntity val, PersistField typ) => expr (Maybe (Entity val)) -> EntityField val typ -> expr (Value (Maybe typ))Source

Project a field of an entity that may be null.

val :: PersistField typ => typ -> expr (Value typ)Source

Lift a constant value from Haskell-land to the query.

isNothing :: PersistField typ => expr (Value (Maybe typ)) -> expr (Value Bool)Source

IS NULL comparison.

just :: expr (Value typ) -> expr (Value (Maybe typ))Source

Analog to Just, promotes a value of type typ into one of type Maybe typ. It should hold that val . Just === just . val.

nothing :: expr (Value (Maybe typ))Source

NULL value.

countRows :: Num a => expr (Value a)Source

COUNT(*) value.

not_ :: expr (Value Bool) -> expr (Value Bool)Source

(==.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)Source

(>=.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)Source

(>.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)Source

(<=.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)Source

(<.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)Source

(!=.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)Source

(&&.) :: expr (Value Bool) -> expr (Value Bool) -> expr (Value Bool)Source

(||.) :: expr (Value Bool) -> expr (Value Bool) -> expr (Value Bool)Source

(+.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a)Source

(-.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a)Source

(/.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a)Source

(*.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a)Source

set :: PersistEntity val => expr (Entity val) -> [expr (Update val)] -> query ()Source

SET clause used on UPDATEs. Note that while it's not a type error to use this function on a SELECT, it will most certainly result in a runtime error.

(=.) :: (PersistEntity val, PersistField typ) => EntityField val typ -> expr (Value typ) -> expr (Update val)Source

(+=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val)Source

(-=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val)Source

(*=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val)Source

(/=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val)Source

from :: From query expr backend a => (a -> query b) -> query bSource

FROM clause: bring an entity into scope.

The following types implement from:

  • Expr (Entity val), which brings a single entity into scope.
  • Tuples of any other types supported by from. Calling from multiple times is the same as calling from a single time and using a tuple.

Note that using from for the same entity twice does work and corresponds to a self-join. You don't even need to use two different calls to from, you may use a tuple.

data Value a Source

A single value (as opposed to a whole entity). You may use (^.) or (?.) to get a Value from an Entity.

Constructors

Value a 

Instances

Typeable1 Value 
Eq a => Eq (Value a) 
Ord a => Ord (Value a) 
Show a => Show (Value a) 
PersistField a => SqlSelect (SqlExpr (Value a)) (Value a) 

data OrderBy Source

Phantom type used by orderBy, asc and desc.

Joins

data InnerJoin a b Source

Data type that represents an INNER JOIN (see LeftOuterJoin for an example).

Constructors

a InnerJoin b 

Instances

IsJoinKind InnerJoin 
(Esqueleto query expr backend, FromPreprocess query expr backend (InnerJoin a b)) => From query expr backend (InnerJoin a b) 

data CrossJoin a b Source

Data type that represents a CROSS JOIN (see LeftOuterJoin for an example).

Constructors

a CrossJoin b 

Instances

IsJoinKind CrossJoin 
(Esqueleto query expr backend, FromPreprocess query expr backend (CrossJoin a b)) => From query expr backend (CrossJoin a b) 

data LeftOuterJoin a b Source

Data type that represents a LEFT OUTER JOIN. For example,

 select $
 from $ (person LeftOuterJoin pet) ->
   ...

is translated into

 SELECT ...
 FROM Person LEFT OUTER JOIN Pet
 ...

Constructors

a LeftOuterJoin b 

Instances

IsJoinKind LeftOuterJoin 
(Esqueleto query expr backend, FromPreprocess query expr backend (LeftOuterJoin a b)) => From query expr backend (LeftOuterJoin a b) 

data RightOuterJoin a b Source

Data type that represents a RIGHT OUTER JOIN (see LeftOuterJoin for an example).

Constructors

a RightOuterJoin b 

Instances

IsJoinKind RightOuterJoin 
(Esqueleto query expr backend, FromPreprocess query expr backend (RightOuterJoin a b)) => From query expr backend (RightOuterJoin a b) 

data FullOuterJoin a b Source

Data type that represents a FULL OUTER JOIN (see LeftOuterJoin for an example).

Constructors

a FullOuterJoin b 

Instances

IsJoinKind FullOuterJoin 
(Esqueleto query expr backend, FromPreprocess query expr backend (FullOuterJoin a b)) => From query expr backend (FullOuterJoin a b) 

SQL backend

data SqlExpr a Source

An expression on the SQL backend.

Instances

Esqueleto SqlQuery SqlExpr SqlPersist 
PersistEntity a => SqlSelect (SqlExpr (Maybe (Entity a))) (Maybe (Entity a)) 
PersistEntity a => SqlSelect (SqlExpr (Entity a)) (Entity a) 
PersistField a => SqlSelect (SqlExpr (Value a)) (Value a) 

select :: (SqlSelect a r, MonadLogger m, MonadResourceBase m) => SqlQuery a -> SqlPersist m [r]Source

Execute an esqueleto SELECT query inside persistent's SqlPersist monad and return a list of rows.

selectDistinct :: (SqlSelect a r, MonadLogger m, MonadResourceBase m) => SqlQuery a -> SqlPersist m [r]Source

Execute an esqueleto SELECT DISTINCT query inside persistent's SqlPersist monad and return a list of rows.

selectSource :: (SqlSelect a r, MonadLogger m, MonadResourceBase m) => SqlQuery a -> SqlPersist m (Source (ResourceT (SqlPersist m)) r)Source

Execute an esqueleto SELECT query inside persistent's SqlPersist monad and return a Source of rows.

selectDistinctSource :: (SqlSelect a r, MonadLogger m, MonadResourceBase m) => SqlQuery a -> SqlPersist m (Source (ResourceT (SqlPersist m)) r)Source

Execute an esqueleto SELECT DISTINCT query inside persistent's SqlPersist monad and return a Source of rows.

delete :: (MonadLogger m, MonadResourceBase m) => SqlQuery () -> SqlPersist m ()Source

Execute an esqueleto DELETE query inside persistent's SqlPersist monad. Note that currently there are no type checks for statements that should not appear on a DELETE query.

Example of usage:

 delete $
 from $ \appointment ->
 where_ (appointment ^. AppointmentDate <. val now)

update :: (MonadLogger m, MonadResourceBase m, PersistEntity val, PersistEntityBackend val ~ SqlPersist) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlPersist m ()Source

Execute an esqueleto UPDATE query inside persistent's SqlPersist monad. Note that currently there are no type checks for statements that should not appear on a UPDATE query.

Example of usage:

 update $ p -> do
 set p [ PersonAge =. just (val thisYear) -. p ^. PersonBorn ]
 where_ $ isNull (p ^. PersonAge)

Re-exports

We re-export Database.Persist.Store for convenience, since esqueleto currently does not provide a way of doing INSERTs.

deleteKey :: (PersistStore backend m, PersistEntity val) => Key backend val -> backend m ()Source

Synonym for delete that does not clash with esqueleto's delete.